home *** CD-ROM | disk | FTP | other *** search
Text File | 1988-08-16 | 93.4 KB | 3,269 lines |
- <<< KERMIT.BUFEMP >>>
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;;;;;;;;;;;;;;;; BUFEMP ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O BUFEMP.(BUFFER,LEN)
-
- ; write out the content of the buffer out to the receiving disk file
- ; BUFFER is an integer array which holds the data
- ; LEN tells how many bytes are there in this buffer array
- ;
- ; NOTE -- the following /INCLUDES refer to files that are included below
- ; without the "BYU.PROG." prefix. There are many /INCLUDES for these files,
- ; so watch out!
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R BUFFER(132),LEN,CH,I,T
-
- # E'E HEXDMPP.(0,LEN,0,BUFFER)
-
- I=0 ;start with the very first charact
- W'E (I.L.LEN) ;put LEN characters into disk file
- T=BUFFER(I) ;get the next character from buffe
- W'R (T.EQ.MYQUOTE) ;is this my quote character
- I=I+1 ;increment the counter
- T=BUFFER(I) ;get next character from buffer
- W'R (T.NE.MYQUOTE), T=CTL.(T) ;is this quote character the
- ;actual QUOTE character
- E'L
- W'R (T.NE.LF), E'E DPUTCH.(T,FD) ;filter out LF
- I=I+1
- E'W
- F'N
- E'N
- <<< KERMIT.BUFILL >>>
- ; 23 jly esj on cr, add lf
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;;;; BUFILL ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O BUFILL.(BUFFER)
-
- ; fill up the buffer with character byte from the sending disk file
- ; BUFFER is used to stored the data from the sending disk file
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R I,BUFFER(132)
-
- I=0
-
- R'T
- E'E DGETCH.(T,FD) ;keep reading byte from the d
- W'R T .E. -1 , B'K ;file until we reach an EOF,o
- ;we have enough byte to fill
- ;buffer, return from within t
- ;directly
- W'R ((T.LT.BLANK).OR.(T.EQ.DEL).OR.(T.EQ.QUOTE))
- W'R (T.EQ.CR) ;it is the line delimiter of
- BUFFER(I)=QUOTE ;this system, insert the CR
- I=I+1 ;before the LF
- BUFFER(I)=CTL.(CR)
- I=I+1
- T = LF ; and put lf in buffer
- E'L
- BUFFER(I)=QUOTE ;we got a character that
- I=I+1 ;quoting
- W'R (T.NE.QUOTE),T=CTL.(T)
- E'L
- BUFFER(I)=T
- I=I+1
- W'R (I.GT.(SPSIZ-8)) ;read up to spsiz-8 byte from disk
- LCLSTATE=I ;I byte was read
- F'N LCLSTATE
- E'L
- F'R
-
- W'R (I.EQ.0)
- LCLSTATE=EOF ;zero byte was read
- F'N LCLSTATE
- O'E
- LCLSTATE=I ;partial EOF was detected
- F'N LCLSTATE
- E'L
- F'N LCLSTATE
- E'N
- <<< KERMIT.CHTOIN >>>
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;; CHTOIN ;;;;;;;;;;;;;;;;;;;;;;;;;;;;C
- E'F A:S(NWLS)
- E'O CHTOIN.(CSTRING,ISTRING,ILENGTH)
-
- ; converts a character string into an integer array, using only the
- ; the last 7 bits, also added an extra EOS into the end of the
- ; integer array string
-
- ; CSTRING is the character string
- ; ISTRING is the integer array which will hold the new string
- ; ILENGTH tell how long the character string is
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R ISTRING(1),ILENGTH
-
- I = 0
- W'E I.L. ILENGTH
- ISTRING(I) = LDBYTT.(CSTRING, I) .LAND. '7F'
- I = I + 1
- E'W
-
- ISTRING(I) = EOS
- F'N
- E'N
- <<< KERMIT.CTL >>>
- ; 18 jly 85 esj converted
- ;;; CTL ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O CTL.(T)
-
- ; toggle the control bit of a character so that
- ; CNTR-A becomes A and vice versa
-
- I'R T
-
- F'N (T .EOR. 64) ;do a exclusive OR on the control bit which is
- ;the seventh th bit
- E'N
- <<< KERMIT.CTOI >>>
- ; 18 jly 85 esj converted
- ;;; CTOI ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O CTOI.(IN, I)
- I'R IN(1)
- I'R I, S
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- LBL0 W'R (.NOT.(IN(I) .EQ. 32 .OR. IN(I) .EQ. 9)), T'O LBL1
- I = I + 1
- T'O LBL0
- LBL1 C'E
- W'R (.NOT.(IN(I) .EQ. 45 .OR. IN(I) .EQ. 43)), T'O LBL2
- S = IN(I)
- I = I + 1
- T'O LBL3
- LBL2 C'E
- S = 0
- LBL3 C'E
- LCLCTOI = 0
- LBL4 W'R (.NOT.(IN(I) .NE. 10002)), T'O LBL6
- W'R (.NOT.(IN(I) .LT. 48 .OR. IN(I) .GT. 57)), T'O LBL7
- T'O LBL6
- LBL7 C'E
- LCLCTOI = 10 * LCLCTOI + IN(I) - 48
- LBL5 I = I + 1
- T'O LBL4
- LBL6 C'E
- W'R (.NOT.(S .EQ. 45)), T'O LBL9
- LCLCTOI = -LCLCTOI
- LBL9 C'E
- F'N LCLCTOI
- E'N
- <<< KERMIT.DODOT >>>
- ; 6 aug 85 esj created
- ;--------------------------< dodot >------------------------------------
- E'F
- E'O DODOT.
- ;-----------------------------------------------------------------------
- ; purpose
- ; to print dots and to add a cr/lf after 79 char if in local mode
- ;
- ; input
- ; none
- ;
- ; output
- ; none
- ;
- ; insert files
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- ;
- ; local static storage
- ; none
- ;
- ; global
- G'L DODOTCT ; count the number of dots sent
- G'L HOSTON ; see kercom
- ;
- ;----------------------< start of code >--------------------------------
-
- W'R (HOSTON.EQ.NO) ;if we are running in local
- E'E TYPOUT.(1,$..$)
- DODOTCT = DODOTCT + 1
- W'R DODOTCT .E. 78
- DODOTCT = 0
- E'E TYPE.(0,0)
- E'L
- E'L
- F'N
- E'N
- <<< KERMIT.IBMGETLN >>>
- ;;;;;;;;;;;;;;;; IBMGETLN ;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O IBMGETLN.(BUFFER,CH)
-
- ; read a packet with a SOH in it and wait for the prompt
- ; before returning it
-
- ; BUFFER is an integer array that will hold the incoming packet
- ; CH tells this routine which channel to read the packet from
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R BUFFER(132),CH,STATUS,GASOH,COUNT,T,IBYTE
- I'R X
-
- STATUS=YES
- GASOH=NO ;we have not gotten a packet yet
- COUNT=1
- W'E (STATUS.EQ.YES)
- W'E (GASOH.EQ.NO) ;keep reading one byte at a tim
- IBYTE=0 ;the I/O port until you see the
- X=TGETCH.(IBYTE,CH) ;character , EOF is not expected
- W'R (IBYTE.EQ.SOH)
- GASOH=YES ;I got the SOH
- BUFFER(COUNT)=IBYTE ;store the SOH into buffer
- COUNT=COUNT+1 ;increment the buffer pointer
- E'L
- E'W
- IBYTE=0
- X=TGETCH.(IBYTE,CH) ;read a byte from the I/O port
- W'R (IBYTE.EQ.PROMPT) ; we got the prompt
- STATUS=NO
- O'E
- BUFFER(COUNT)=IBYTE ;it is not a prompt, but another
- COUNT=COUNT+1 ;data of the incoming packet
- E'L ;store it and increment pointer
- E'W
- BUFFER(COUNT)=EOS ;add an EOS into end of buffer
- LCLSTATE=OK
- F'N LCLSTATE
- E'N
- <<< KERMIT.INSTALL >>>
- *
- * THIS FILE WILL COMPILE AND LOAD CODE NEEDED FOR CV-KERMIT.
- *
- *-------------------------------------------------------------------------
- COMPILE BYU.PROG.KERMIT.BUFEMP
- COMPILE BYU.PROG.KERMIT.BUFILL
- COMPILE BYU.PROG.KERMIT.CHTOIN
- COMPILE BYU.PROG.KERMIT.CTL
- COMPILE BYU.PROG.KERMIT.CTOI
- COMPILE BYU.PROG.KERMIT.DODOT
- COMPILE BYU.PROG.KERMIT.IBMGETLN
- COMPILE BYU.PROG.KERMIT.KGETLIN
- COMPILE BYU.PROG.KERMIT.KMAIN
- COMPILE BYU.PROG.KERMIT.NEXTFILE
- COMPILE BYU.PROG.KERMIT.PACK
- COMPILE BYU.PROG.KERMIT.PARSER
- COMPILE BYU.PROG.KERMIT.PUTLIN
- COMPILE BYU.PROG.KERMIT.RDATA
- COMPILE BYU.PROG.KERMIT.RECSW
- COMPILE BYU.PROG.KERMIT.RFILE
- COMPILE BYU.PROG.KERMIT.RINIT
- COMPILE BYU.PROG.KERMIT.RPACK
- COMPILE BYU.PROG.KERMIT.RPAR
- COMPILE BYU.PROG.KERMIT.SBREAK
- COMPILE BYU.PROG.KERMIT.SCONNECT
- COMPILE BYU.PROG.KERMIT.SCOPY
- COMPILE BYU.PROG.KERMIT.SDATA
- COMPILE BYU.PROG.KERMIT.SENDSW
- COMPILE BYU.PROG.KERMIT.SEOF
- COMPILE BYU.PROG.KERMIT.SETCOOK
- COMPILE BYU.PROG.KERMIT.SETPORT
- COMPILE BYU.PROG.KERMIT.SETRAW
- COMPILE BYU.PROG.KERMIT.SFILE
- COMPILE BYU.PROG.KERMIT.SHELP
- COMPILE BYU.PROG.KERMIT.SINIT
- COMPILE BYU.PROG.KERMIT.SPACK
- COMPILE BYU.PROG.KERMIT.SPAR
- COMPILE BYU.PROG.KERMIT.SQUIT
- COMPILE BYU.PROG.KERMIT.SRECEIVE
- COMPILE BYU.PROG.KERMIT.SSEND
- COMPILE BYU.PROG.KERMIT.SSET
- COMPILE BYU.PROG.KERMIT.SSTATUS
- COMPILE BYU.PROG.KERMIT.TEXT-FILE-IO
- COMPILE BYU.PROG.KERMIT.TGETCH
- COMPILE BYU.PROG.KERMIT.TOCHAR
- COMPILE BYU.PROG.KERMIT.TPUTCH
- COMPILE BYU.PROG.KERMIT.UN&PACK
- COMPILE BYU.PROG.KERMIT.UNCHAR
- COMPILE BYU.PROG.KERMIT.XDELAY
- *
- *
- *
- SYSLOAD BYU.PROG.KERMIT.MAKE
- GENCOMIX
-
- COPYTEXT BYU.PROG.KERMIT.SYSNEWS SYSNEWS.COMMAND.KERMIT//REPLACE=NEWER
- <<< KERMIT.KGETLIN >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;;;;;;; KGETLIN ;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O KGETLIN.(BUFFER,UNIT)
-
- ; read a packet with a SOH in it and DON'T wait for the prompt
- ; before returning it
-
- ; BUFFER is an integer array that will hold the incoming packet
- ; UNIT tells this routine which device to read the packet from
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R BUFFER(*),STATUS,GASOH,COUNT,IBYTE
- I'R X,LCLSTATE
-
- ; E'E TYPEHEX.(.ADDR.BUFFER)
- STATUS=YES
- GASOH=NO ;we have not gotten a packet yet
- COUNT=0
- W'E (STATUS.EQ.YES)
- IBYTE=0
- X=TGETCH.(IBYTE,UNIT) ;read a byte from the I/O port
- W'R (IBYTE.EQ.MYEOL .AND. GASOH .E. YES) ;we got the required MYEOL
- STATUS=NO
- O'R (IBYTE .E. SOH)
- BUFFER(0)=IBYTE ;store the SOH into buffer
- COUNT = 1 ; rest buffer pointer to first soh
- GASOH = YES
- O'R (GASOH .E. YES) ; get char into buffer iff gasoh=yes
- BUFFER(COUNT)=IBYTE ;it is not MYEOL, but another
- COUNT=COUNT+1 ;data of the incoming packet
- E'L ;store it and increment pointer
- E'W
- BUFFER(COUNT)=EOS ;add an EOS into end of buffer
- LCLSTATE=OK
- ; E'E TYPOUT.(2,$KL$)
- ; E'E TYPEHEX.(COUNT)
- ; E'E TYPEHEX.(.ADDR.(BUFFER(COUNT)))
- ; E'E STACKDMP.
- F'N LCLSTATE
- E'N
- <<< KERMIT.KMAIN >>>
- ; 15-AUG-85 MVI: CHANGED NO IOFLAG VALUE FROM 0 TO -1.
- ; 7 aug 85 dg/esj added no wait io support
- ; 17 jly 85 esj converted
- ;;;;;;;;;;;;;; KMAIN ;;;;;;;;;;;;;;;;;;;;;;;
- ;
- E'F A:S(NWLS)
- E'O KMAIN.
-
- ; CGOS-KERMIT MAIN PROGRAM
-
- ; CGOS KERMIT was converted from hp1000 kermit
- ; guilty parties: esj, lec, pcc
- ; cohort in crime: mvi
-
- ; HP1000 KERMIT was implemented by John Lee of RCA Laboratories
- ; 6/29/84
-
- ; Permission is granted to any individual or instution to copy
- ; or use this program, except for explicitly commerical purpose.
-
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
-
- G'L VENQACK,VXONXOFF
- G'L VERNUM
-
-
- * FORMATS TRANSFORMED TO V:S
- V'S F99 = $ CGOS KERMIT Version!$
- V'S F100 = $ Remote Host KERMIT mode now in effect!$
-
- DELAY = 15 ; 15 SECONDS
- EOL = 13 ; CR
- ESCHAR = 29 ; CNTR-]
- HOSTON = YES ; we are running in Remote Host mode
- IBMON = NO
-
- ; set up no wait io for terminal io
- LOCALDEV = $SD$ ; default comdev
- LOCALDEV(1) = -1 ; no io flag yet
- RMTDEV = $SD$ ; default kermit device name since we wake up in
- RMTDEV(1) = -1 ; no io flag yet
- MAXTRY = 5 ; remote mode
- MYEOL = 13
- MYPAD = 0
- MYPCHAR = 0
- MYQUOTE = 35
- PAD = 0
- PADCHAR = 0
- PAKSIZ = 80
- PROMPT = 17 ;DC1, IBM MODE ONLY
- QUOTE = 35
- SOH = 1
- STATE = BIGC
- SPARITY = NO
- SBAUD = NO
- SPORT = YES
- VXONXOFF = 1 ;set XON/XOFF enabled
- VENQACK = 0 ;set ENQ/ACK disabled
- ;
-
-
- ; determine whether we are running in Remote or Local KERMIT mode
- HOSTON = YES ;remote kermit in effect
- E:E TYPMSG.(F99)
- E:E TYPEMSG.(VERNUM)
- E:E TYPEMSG.(F100)
-
- E'E PARSER.
- F'N
- E'N
- <<< KERMIT.MAKE >>>
- * 16 sep 86 cdo; copied to the byu catalog
- * 12 sep 85 esj changed loadsym to janmake.symfile.universe
- * 26 aug 85 esj added loadlib.kermit and globals dodotct and lclchq
- * 6 aug 85 esj birthday
- *---------------------< cvcommand.make.command.kermit >---------------------
- *
- *
- *
- *load symbol files & insert equate files
- *---------------------------------------
- loadsym janmake.symfile.universe
- *
- *
- *
- *define object code block
- *------------------------
- equ &blksiz 3000
- equ &blktop &command+&blksiz
- *
- *
- *
- *define common area (globals) block
- *----------------------------------
- equ &gvsiz 2000
- equ &gvtop &blktop+&gvsiz
- *
- *
- *
- *define misc: sort buffers or temp buffer.......
- *-----------------------------------------------
- equ &remspac &cortop - &gvtop - 100
- if &remspac > 1000
- equ &arraysz 1000
- else
- equ &arraysz &remspac
- endc
- *
- *
- *
- *define start : code is loaded from
- *----------------------------------
- cororg &command
- *
- *
- *
- block &gvtop,&cortop ;(misc area)
- *---------------------------------
- *
- *
- *
- block &blktop,&gvtop ;(common area)
- *----------------------------------
- print " loading globals "
-
- global fd(100), ifd(100), ifdflg(1)
- global delay(1), eol(1), eschar(1), filname(85), hoston(1)
- global ibmon(1), maxtry(1), myeol(1)
- global mypad(1), mypchar(1), myquote(1), n(1), numtry(1)
- global oldtry(1), packet(85), pad(1), padchar(1), paksiz(1)
- global parity(1), prompt(1), quote(1), recpkt(85)
- global rmtdev(2), localdev(2)
- global rmttty(85), rpsiz(1), sbaud(1), size(1)
- global soh(1), sparity(1), speed(1), sport(1), spsiz(1), state(1)
- global venqack(1), vxonxoff(1)
- global xnew(1), xcount(1), xeof(1)
- global tpname(84), timeout(2), dodotct(1), lclchq(1001)
- *
- block &command,&blktop ;(object code block)
- *------------------------------------------
-
- print " loading code "
- *
- calltv kmain
- *
- * MUST BE INCLUDED WITH EVERY SUBMISSION!
- insert byu.prog.kermit.version-log
- *
- *load subroutines
- *-----------------------------------------
- load byu.prog.kermit/kmain, bufemp, bufill, chtoin, ctl, ctoi
- load byu.prog.kermit/ibmgetln, kgetlin
- load byu.prog.kermit/pack, parser, putlin, rdata
- load byu.prog.kermit/recsw, rfile, rinit
- load byu.prog.kermit/rpack, rpar, sbreak
- load byu.prog.kermit/scopy, sdata, sendsw, seof
- load byu.prog.kermit/setcook, setport, setraw
- load byu.prog.kermit/sinit, spack, spar
- load byu.prog.kermit/squit, sreceive, nextfile
- load byu.prog.kermit/text-file-io, tgetch, tochar, tputch, un&pack
- load byu.prog.kermit/unchar, sfile, shelp, dodot
- load byu.prog.kermit/sconnect, ssend, sset, sstatus, xdelay
-
- *load all undefined referenced subroutines
- *-----------------------------------------
-
- print " loading loadlibs "
-
- lib byu.prog.kermit.loadlib.kermit
- lib loadlib.oslib
- *
- *
- *
- *define: referencing command name or dloc
- *----------------------------------------
- if debug = -1
- filename kermee
- else
- filename =cvscommand.kermit
- endc
- cwrite &blksiz,&command,&cortop
- <<< KERMIT.NEXTFILE >>>
- ; 7 aug 85 esj created
- ;--------------------------< nextfile >---------------------------------
- E'F
- E'O NEXTFILE.( FILEDESC, FNAME)
- ;-----------------------------------------------------------------------
- ; purpose
- ; to get the next file name from the file specified in fd
- ;
- ; input
- I'R FILEDESC(*) ; descriptor of the file containing names
- ;
- ; output
- I'R FNAME(*) ; cgos format filename. fname will = 0 when there
- ; are no more files to be opened
- ;
- ; insert files
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- ;
- ; local static storage
- I'R CHAR
- ;
- ; global
- ; none
- ;
- ;----------------------< start of code >--------------------------------
- FNAME(0) = 0
- R'T
- E'E DGETCH.(CHAR, FILEDESC)
- W'R CHAR .E. '0D' .OR. CHAR .E. -1
- E'E PACKLINE.($! $, FNAME)
- B'K
- E'L
- E'E PACKLINE.(CHAR,FNAME)
- F'R
-
- # E'E TYPE.(0,0)
- # E'E HEXDMP.(FNAME, FNAME+FNAME+1, FNAME, FNAME)
-
- W'R CHAR .E. -1
- E'E CLOSTEXT.(FILEDESC)
- FNAME = 0
- E'L
-
- F'N GOOD
- E'N
- <<< KERMIT.PACK >>>
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;; PACK ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O PACK.(XFROM,XTO)
-
- ; pack the integer array of XFROM into the array of XTO
-
- ; input
- I'R XFROM(*) ; string in kermit format
-
- ; output
- I'R XTO ; array XTO is a cv format string array
-
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I = 0
- XTO = 0
-
- W'E XFROM(I) .NE. EOS
- E'E PACKLINE.(XFROM(I), XTO)
- I = I + 1
- E'W
- F'N
- E'N
- <<< KERMIT.PARSER >>>
- ; 16 aug 85 esj remove server commands that were added as aliases
- ; 12 aug 85 esj add extra aliases
- ; 6 aug 85 esj set dot count to 0 on every command
- ; 26 jly 85 esj detach kermit port on quit.
- * 15-Jul-85 lec; TPL conversion.
- ;--------------------------------------< parser >---------------------------
- E:F
- E'O PARSER.
- ;----------------------------------------------------------------------------
- ;
- ; Purpose
- ; the main parser at the command level of kermit
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Inserts
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- ; Globals
- G'L HOSTON
- G'L DODOTCT
-
- ; Locals
- I'R BLIN(132)
- I'R STATUS
- I:R OPTION(4)
-
- ; Method
- ; initialize keyword character string
-
- ; convert character string to integer array with an EOS at end
- ; of the integer array
-
- ; do forever
-
- ;---------------------------< start of code >-------------------------------
-
- STATUS=YES
-
- W'E (STATUS.EQ.YES)
- ; set dot count to 0
- DODOTCT = 0
-
- W'R HOSTON .E. YES
- ; when running local kermit, put prompt in caps
- E'E TYPOUT.(9, $KERMIT-CV$)
- O'E
- ; when running remote kermit, put prompt in lowercase
- E'E TYPOUT.(9, $kermit-cv$)
- E'L
- W:R NEWCMD.($> $,1,0) .G. 0
- E:E IDENT.(OPTION)
-
- ;it is the keyword CONNECT
- W'R COMPNAM.(OPTION,$CONNECT $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$CON $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$C $) .E. 0
- E'E SCONNECT.
-
- ;it is the keyword QUIT or EXIT
- O'R COMPNAM.(OPTION,$QUIT $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$EXIT $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$Q $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$E $) .E. 0
- E'E DETACH.($KM$)
- E:E TYPEMSG.($Leaving KERMIT now...!$)
- STATUS = $NO$
-
- ;it is the keyword HELP
- O'R COMPNAM.(OPTION,$HELP $) .E. 0
- E'E SHELP.
-
- ;it is the keyword RECEIVE
- O'R COMPNAM.(OPTION,$RECEIVE $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$REC $) .E. 0 .OR.
- 1 COMPNAM.(OPTION,$R $) .E. 0
- E'E SRECEIVE.
-
- ;it is the keyword SET
- O'R COMPNAM.(OPTION,$SET $) .E. 0
- E'E SSET.(BLIN)
-
- ;it is the keyword SEND
- O'R COMPNAM.(OPTION,$SEND $) .E. 0
- E'E SSEND.
-
- ;it is the keyword STATUS
- O'R COMPNAM.(OPTION,$STATUS $) .E. 0
- E'E SSTATUS.
-
- O'E
- E:E TYPEMSG.($Unrecognized command type "HELP"!$)
- E'L
- E:L
- E'W
-
- F'N
- E:N
- <<< KERMIT.PUTLIN >>>
- ; 07 AUG 85 DG IOFLAG IS PART OF UNIT
- ; ADDED NO WAIT I/O SUPPORT
- ; 18 jly 85 esj
- ;-------------------------------< putlin >-------------------------------
- E'F A:S(NWLS)
- E'O PUTLIN.(ALIN,UNIT)
- ;------------------------------------------------------------------------
- ; output a line ot the specific channel
-
- ; input
- I'R ALIN ; line in kermit format to be output
- I'R UNIT(1) ; UNIT(0) unit we want to send I/O to
- ; UNIT(1) I/O flag for the unit
-
- ; output
- ; none
-
- ; local storage
- I'R ARGLIST(3)
- I'R LINE(80) ; temp line storage
-
- ; insert files
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
-
- ;------------------------< start of executable code >-----------------------
-
- LINE(0) = 0
- E'E PACK.(ALIN, LINE)
-
- ARGLIST(0) = 0
- ARGLIST(1) = LINE(0)
- ARGLIST(2) = 0
-
- W'R UNIT(1) .NE. 0
- ; non zero means not first time through for this unit
-
- W:R TESTIO.(UNIT(1)).E.0 ;I/O IN PROGRESS FROM LAST REQUEST
- E:E WAITIO.(UNIT(1)) ;WAIT FOR I/O TO FINISH
- E:L
- E'L
-
- UNIT(1) = CONTROL.( UNIT, ARGLIST, LINE(1), 0 )
-
- F'N
- E'N
- <<< KERMIT.RDATA >>>
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;;; RDATA ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O RDATA.(X)
-
- ; read a data packet from the other KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R NUM,LEN,STATUS,X,TNUM
- I'R TV1,TV2,TV3,TV4
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded maxtry , gives up
- E'E CLOSTEXT.(FD)
-
- O'E
- NUMTRY=NUMTRY+1 ;try it again
- STATUS=RPACK.(LEN,NUM,PACKET) ;read a packet
-
- E'E DODOT. ; tell all if ok to
-
- W'R (STATUS.EQ.BIGD) ;we got the data packet
- W'R (NUM.NE.N)
- W'R (OLDTRY.GT.MAXTRY)
- LCLSTATE=BIGA
- E'E CLOSTEXT.(FD)
- O'E
- OLDTRY=OLDTRY+1
- W'R (NUM.EQ.(N-1))
- E'E SPAR.(PACKET) ;we got a duplicted packet
- TV1=BIGY ;just ACK it
- TV2=6
- E'E SPACK.(TV1,NUM,TV2,PACKET)
- NUMTRY=0
- LCLSTATE=STATE
- O'E
- LCLSTATE=BIGA
- E'E CLOSTEXT.(FD)
- E'L
- E'L
-
- O'E
- E'E BUFEMP.(PACKET,LEN) ;write the data packet just receive
- TNUM=N ;into the receiving disk file
- TV1=BIGY
- TV2=TNUM
- TV3=0
- TV4=0
- E'E SPACK.(TV1,TV2,TV3,TV4) ;ACK the just received packet
- OLDTRY=NUMTRY
- NUMTRY=0
- N=(N+1) .MOD. 64
- LCLSTATE=BIGD
- E'L
-
- O'R (STATUS.EQ.BIGF) ;the packet is the file header
- W'R (OLDTRY.GT.MAXTRY) ;we should have already gotten
- LCLSTATE=BIGA ;exceeded number of retry, give
- E'E CLOSTEXT.(FD)
-
- O'E
- OLDTRY=OLDTRY+1
- W'R (NUM.EQ.(N-1)) ;we got duplicate file header p
- TV1=BIGY
- TV2=0
- TV3=0
- E'E SPACK.(TV1,NUM,TV2,TV3) ;just ACK it
- NUMTRY=0
- LCLSTATE=STATE
-
- O'E
- LCLSTATE=BIGA
- E'E CLOSTEXT.(FD)
-
- E'L
- E'L
-
- O'R (STATUS.EQ.BIGZ) ;we got the EOF packet
- W'R (NUM.NE.N)
- LCLSTATE=BIGA
- E'E CLOSTEXT.(FD)
- O'E
- TNUM=N
- TV1=BIGY
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;ACK it
- E'E CLOSTEXT.(FD) ;close the receiving disk fi
- N = (N+1) .MOD. 64
- LCLSTATE=BIGF ;change the state to look fo
- E'L
-
- O'R (STATUS.EQ.BAD)
- LCLSTATE=STATE ;there was an error in the
- TNUM=N ;checksum
- TV1=BIGN
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;NAK it
-
- O'E
- LCLSTATE=BIGA ;we got a unknown packet type
- E'E CLOSTEXT.(FD)
- E'L ;gives up
- E'L
- F'N LCLSTATE
- E'N
- <<< KERMIT.RECSW >>>
- ; 17 jly 85 esj converted
- ;;;;;;;;;;;;; RECSW ;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O RECSW.(X)
-
- ; receive a file or a group of file from the other KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- G'L XNEW,XCOUNT
- I'R X,STATUS
- I'R TV1,TV2,TV3,TV4
-
- STATUS=YES
- STATE=BIGR
- XNEW=YES
- XCOUNT=1
- N=0
- NUMTRY=0
- W'E (STATUS.EQ.YES)
- # E'E TYPOUT.(2,'A000'.LOR.STATE)
- # E'E TYPEMSG.($ is current state!$)
-
- W'R (STATE.EQ.BIGD) ;read a DATA packet
- STATE=RDATA.(X)
-
- O'R(STATE.EQ.BIGR) ;read a SINIT packet
- STATE=RINIT.(X)
-
- O'R(STATE.EQ.BIGF) ;read a file header
- STATE=RFILE.(X)
-
- O'R(STATE.EQ.BIGC) ;file transfer compl
- LCLSTATE=YES
- F'N LCLSTATE
-
- O'R(STATE.EQ.BIGA) ;we got an error
- LCLSTATE=NO
- TV1=BIGE
- TV2=N
- TV3=0
- TV4=0
- E'E SPACK.(TV1,TV2,TV3,TV4) ;send an ERROR packe
- F'N LCLSTATE ;file channel
- E'L
- E'W
- F'N LCLSTATE
- E'N
- <<< KERMIT.RFILE >>>
- ; 17 jly 85 esj converted
- ;----------------------------------------< rfile >--------------------------
- E'F A:S(NWLS)
- E'O RFILE.(X)
- ;----------------------------------------------------------------------------
- ;
- ; Purpose
- ; read a file header packet from the other KERMIT
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Inserts
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- ; Globals
- ; none
-
- ; Locals
- I'R NUM,LEN,STATUS,LCLSTATE,X,TNUM
- I'R TV1,TV2,TV3,TV4,XWRITE
-
- ;---------------------------< start of code >-------------------------------
-
- XWRITE=1
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max. # of re-try
- F'N LCLSTATE ;gives up
- O'E
- NUMTRY=NUMTRY+1
- E'L
- STATUS=RPACK.(LEN,NUM,PACKET)
- W'R (STATUS.EQ.BIGS) ;we got a SINIT packet
- W'R (OLDTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;re-try it again
- F'N LCLSTATE
- O'E
- OLDTRY=OLDTRY+1
- E'L
-
- W'R (NUM.EQ.(N-1)) ;we already got the SINIT
- E'E SPAR.(PACKET) ;packet, get my file-transf
- TV1=BIGY ;requirement/parameters
- TV2=6
- E'E SPACK.(TV1,NUM,TV2,PACKET) ;ACK it
- NUMTRY=0
- LCLSTATE=STATE
- F'N LCLSTATE
-
- O'E
- LCLSTATE=BIGA ;unexpected sequence #
- F'N LCLSTATE ;gives up
- E'L
-
- O'R (STATUS.EQ.BIGZ) ;we got a EOF packet
- W'R (OLDTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max # of re-try
- F'N LCLSTATE ;gives up
-
- O'E
- OLDTRY=OLDTRY+1 ;re-try one more time
- E'L
-
- W'R (NUM.EQ.(N-1))
- TV1=BIGY ;we already got the EOF pac
- TV2=0
- TV3=0
- E'E SPACK.(TV1,NUM,TV2,TV3) ;just ACK it
- NUMTRY=0
- LCLSTATE=STATE
- F'N LCLSTATE
-
- O'E
- LCLSTATE=BIGA ;unexpected sequence #
- F'N LCLSTATE
- E'L
-
- O'R (STATUS.EQ.BIGF) ;we got the file header pac
- W'R (NUM.NE.N)
- LCLSTATE=BIGA ;unexpected sequence #,give
- F'N LCLSTATE
- E'L
-
- PACKET(LEN)=EOS ;filename packet
- W'R (HOSTON.EQ.NO)
- E'E TYPE.(0,0)
- E:E TYPMSG.($Receiving !$)
- E'E PUTLIN.(PACKET,LOCALDEV) ;display the incoming file
- E'E TYPE.(0,0)
- E'L
-
- ERR = OPENTEXT.(PACKET,$SU$, $KM$, FD) ;open that file for writing
- W'R (ERR.NE.0)
- LCLSTATE=BIGA ;we got a ERR in opening th
- F'N LCLSTATE
- E'L
-
- TNUM=N
- TV1=BIGY
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;ACK the file header packet
- OLDTRY=NUMTRY
- NUMTRY=0
- N=(N+1) .MOD. 64
- LCLSTATE=BIGD ;change state to look for DA
- F'N LCLSTATE ;packet
-
- O'R (STATUS.EQ.BIGB) ;we got a BREAK transmission
- W'R (NUM.NE.N)
- LCLSTATE=BIGA
- F'N LCLSTATE
- E'L
-
- TNUM=N
- TV1=BIGY
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;ACK the BREAK packet
- LCLSTATE=BIGC ;change state to complete sta
- F'N LCLSTATE
-
- O'R (STATUS.EQ.BAD) ;we got an error on the check
- LCLSTATE=STATE
- TNUM=N
- TV1=BIGN
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;NAK it
- F'N LCLSTATE
- O'E
- LCLSTATE=BIGA ;unexpected packet type, give
- E'L
- F'N LCLSTATE
- E'N
- <<< KERMIT.RINIT >>>
- ; 17 jly 85 esj converted
- ;;;;; RINIT ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O RINIT.(X)
-
- ; receive the initial packet from the remote KERIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R LEN,NUM,STATUS,LCLSTATE,X,TNUM
- I'R TV1,TV2,TV3
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max. # of re-try
- F'N LCLSTATE ;gives up
- O'E
- NUMTRY=NUMTRY+1 ;try-it again
- E'L
-
- E'E FILL.(40,0,PACKET)
-
- STATUS=RPACK.(LEN,NUM,PACKET) ;read a packet
- W'R (STATUS.EQ.BIGS) ;we got a SINIT packet
- E'E RPAR.(PACKET) ;store other KERMIT's requ
- E'E SPAR.(PACKET) ;get our parameters/requir
- TNUM=N
- TV1=BIGY
- TV2=6
- E'E SPACK.(TV1,TNUM,TV2,PACKET) ;send out requirement and
- OLDTRY=NUMTRY ;ACK it on one shot
- NUMTRY=0
- N=((N+1).MOD.64)
- LCLSTATE=BIGF ;change state to look for
- F'N LCLSTATE ;the file header packet
-
- O'R(STATUS.EQ.BAD) ;we got a checksum error
- LCLSTATE=STATE
- TNUM=N
- TV1=BIGN
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;NAK it
- F'N LCLSTATE
-
- O'E
- LCLSTATE=BIGA ;we got an unexpected pack
- E'L ;type, gives up
-
- F'N LCLSTATE
- E'N
- <<< KERMIT.RPACK >>>
- ; 16 jly 85 esj converted
- ;;;;;; RPACK ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O RPACK.(LEN,NUM,XDATA)
-
- ; read a packet from other KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R LEN,NUM,UNIT
- I'R XDATA(1)
- I'R COUNT,STATUS,J,K,T
- I'R TV1,TV2,TV3, LCLSTATE
- I'R BUFFER(132),CHKSUM,XTYPE,GAPTRY,MGAPTRY
-
- G'L TIMEOUT(1) ; temp for lblset call
-
- ;------------------------------< debugging stubs >----------------------------
-
- # LEN = 0
- # NUM = N
- # XDATA = 0
- # E'E TGETCH.(XTYPE,$SD$)
- # E'E FILL.(132,0,XDATA)
- # F'N XTYPE
-
- ;------------------------------< real code >----------------------------
- ; setup lblset for handling deadlock condition
- E'E LBLSET.(TIMEOUT, WAYOUT)
-
- UNIT=RMTDEV ;this is the input channel to
- ;a packet from
- GAPTRY=1
- MGAPTRY=2
- CHKSUM=0
-
- ; read me a packet that begins with a SOH and ends with MYEOL
-
- W'E (GAPTRY.LE.MGAPTRY)
- W'R (IBMON.EQ.YES)
- STATUS=IBMGETLN.(BUFFER,UNIT) ;get a packet and waits for t
- O'E ;prompt
- STATUS=KGETLIN.(BUFFER,UNIT) ;get a packet without waitin
- E'L ;for a prompt
- ; E'E HEXDMP.(0,45,0,BUFFER)
-
- COUNT=0
-
- ; skips all other characters until we see one with a SOH in it
-
- W'E ((BUFFER(COUNT).NE.SOH).AND.(BUFFER(COUNT).NE.EOS))
- COUNT=COUNT+1 ;wait for a SOH or EOS
- E'W
- W'R (BUFFER(COUNT).EQ.SOH) ;we got the SOH
-
- ; we got a line that begins with a SOH
-
- K=COUNT+1
- CHKSUM=BUFFER(K)
- LEN=UNCHAR.(BUFFER(K))-3 ;get the length of the packet
-
- K=K+1
- CHKSUM=CHKSUM+BUFFER(K)
- NUM=UNCHAR.(BUFFER(K)) ;get the sequence number of
- ;the frame packet
- K=K+1
- XTYPE=BUFFER(K) ;get the data type
- CHKSUM=CHKSUM+BUFFER(K)
- K=K+1
-
- ; get the data
-
- ; ZERO OUT THE XDATA ARRAY
- ; E'E FILL.(132,0,XDATA)
-
- T'H L1 FOR J=0, 1, J .GE. LEN
- XDATA(J)=BUFFER(K)
- CHKSUM=CHKSUM+BUFFER(K)
- K=K+1
- L1 C'E
- COUNT = J
-
- XDATA(COUNT+1)=EOS
- T=BUFFER(K)
-
- ; calculate the checksum of the incoming packet
-
- TV1=CHKSUM.LAND.192
- TV2=TV1/64
- TV3=CHKSUM+TV2
- CHKSUM=TV3.LAND.63
-
- ; does the checksum matches
-
- W'R (CHKSUM.NE.UNCHAR.(T))
- # E'E TYPEMSG.($ BAD CHECKSUM !$)
- LCLSTATE=BAD ;bad checksum
- F'N LCLSTATE
-
- O'E
- LCLSTATE=XTYPE
- F'N LCLSTATE
- E'L
- E'L
-
- ; we got the EOS, the packet has no SOH, read another one
-
- GAPTRY=GAPTRY+1
- E'W
- # E'E TYPEMSG.($ SOME OTHER BAD STATE !$)
- LCLSTATE=BAD
- F'N LCLSTATE
-
- WAYOUT F'N BAD ; wayout of a deadlock situation
-
- E'N
- <<< KERMIT.RPAR >>>
- ;16 jly 85 esj converted
- ;;;;;;;;;;;;; RPAR ;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O RPAR.(XDATA)
-
- ; store the other KERMIT's file transfer requirement away
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R XDATA(*)
- I'R DMY(5)
-
- W'R (XDATA(0).EQ.0) ;if the other KERMIT did not s
- SPSIZ=PAKSIZ ;any parameters, default them
- ;our setting; otherwise use wh
- ;the other KERMITs sends
- O'E
- DMY(0) = SPSIZ=UNCHAR.(XDATA(0))
- E'L
- W'R (XDATA(2).NE.0), DMY(1) = PAD=UNCHAR.(XDATA(2))
-
- W'R (XDATA(3).NE.0), DMY(2) = PADCHAR=CTL.(XDATA(3))
-
- W'R (XDATA(4).NE.0), DMY(3) = EOL=UNCHAR.(XDATA(4))
-
- W'R (XDATA(5).NE.0), DMY(4) = QUOTE=XDATA(5)
-
- # E'E HEXDMPP.(5,11,5,DMY)
- F'N
- E'N
- <<< KERMIT.SBREAK >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;; SBREAK ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SBREAK.(X)
-
- ; send the break packet to signify the end of transmissions
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R NUM,LEN,STATUS,X,TNUM
- I'R TV1,TV2,TV3
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max. # of re-
- F'N LCLSTATE ;gives up
- O'E
- NUMTRY=NUMTRY+1 ;try it again
- E'L
-
- TNUM=N
- TV1=BIGB
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3)
- STATUS=RPACK.(LEN,NUM,RECPKT)
-
- W'R (STATUS.EQ.BIGN) ;we got a NAK packet
- W'R (N.NE.(NUM-1))
- LCLSTATE=STATE
- F'N LCLSTATE
- E'L
-
- O'R (STATUS.EQ.BIGY) ;we got a ACK packet
- W'R (N.NE.NUM)
- LCLSTATE=STATE ;but it is out of seque
- F'N LCLSTATE
- E'L
- NUMTRY=0
- N=(N+1).MOD.64
- LCLSTATE=BIGC ;change state to comple
- F'N LCLSTATE ;status
-
- O'R (STATUS.EQ.BAD)
- LCLSTATE=STATE
- F'N LCLSTATE
-
- O'E
- LCLSTATE=BIGA ;receive unknown packet
- E'L ;type or error packet
- F'N LCLSTATE
- E'N
- <<< KERMIT.SCONNECT >>>
- * 14 aug 85 esj attempt to use a queue structure to prevent dropping
- * characters in connect mode
- * 18-jul-85 pcc; fix so it compiles
- *
- *************************************** CVCOMMAND.KERMIT.SCONNECT ******
- *
- E:F A:S(NWLS)
- E:O SCONNECT.
- *
- ************************************************************************
- *
- *
- * Allows the local KERMIT to act as a dumb terminal connected to
- * another computer.
- *
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- *
- EQU LCLQSIZ = 1000
- EQU RMTQSIZ = 10
- *
- I'R TISUNIT
- I'R TISTYPE
- I'R COUNT
- I'R CHBUF
- I'R STATUS
- G'L LCLCHQ(LCLQSIZ) ; char queues for local and remote devices
- I'R RMTCHQ(RMTQSIZ)
- I'R LCLQPTRI ; index to next empty spot in queue
- I'R RMTQPTRI
- I'R LCLQPTRO ; index to next char to be dumped in queue
- I'R RMTQPTRO
-
-
- *Formats to V:S
- V:S F101 = $ To exit from CHAT mode; type control-!$
- *
- ******************* start of executable code ***************************
- *
- STATUS=YES
-
- E:E TYPMSG.(F101)
- CHBUF = CTL.(ESCHAR)
- E'E TYPE.(1,CHBUF.LSH.8)
-
- E'E TRANSPAR.
-
- ; start up the queue structures
- LCLQPTRI = LCLQPTRO = 0
- RMTQPTRI = RMTQPTRO = 0
-
- ; start up the io flags
- LOCALDEV(1) = -1
- RMTDEV(1) = -1
-
- ; r't
- ; w'r there is input
- ; input char
- ; did char come from localdev?
- ; yes --> is it the escape char?
- ; yes --> punt to exit
- ; no --> send to rmtdev queue
- ; no --> it came from the rmtdev
- ; send it to the localdev queue
- ; e'l
- ; w'r lcldev is not busy and lcldev queue is not empty
- ; send char to lcldev
- ; e'l
- ; w'r rmtdev is not busy and rmtdev queue is not empty
- ; send char to rmtdev
- ; e'l
- ; f'r
-
- R'T
- W'E CHKINPUT.(TISUNIT,COUNT) .E. 0
- E'E INPUT.(TISUNIT, TISTYPE, COUNT, CHBUF)
-
- W'R TISUNIT .E. LOCALDEV
- W'R CHBUF .E. ESCHAR
- T'O DONE
- O'E
- ; E'E TPUTCH.(CHBUF, RMTDEV)
- ; put the char on the queue and ignore overflow condition for now
- RMTCHQ(RMTQPTRI) = CHBUF
- RMTQPTRI = (RMTQPTRI + 1) .MOD. RMTQSIZ
- # E'E HEXDMP.(1,11,1,RMTCHQ(RMTQPTRO))
-
- E'L
-
- O'E
- ; E'E TPUTCH.(CHBUF, LOCALDEV)
- ; put the char on the queue and ignore overflow condition for now
-
- LCLCHQ(LCLQPTRI) = CHBUF
- LCLQPTRI = (LCLQPTRI + 1) .MOD. LCLQSIZ
- # E'E HEXDMP.(0,10,0,LCLCHQ(LCLQPTRO))
- E'L
- E'W
-
- ; if the queue is not empty and there is no io in progress or
- ; this is the first time through the io loop, print a char
- W'R LCLQPTRI .NE. LCLQPTRO
- # E'E HEXDMP.(0,1,0,LOCALDEV)
- W'R LOCALDEV(1) .E. -1
- ; this is for the first time through
- E'E TPUTCH.(LCLCHQ(LCLQPTRO), LOCALDEV)
- LCLQPTRO = (LCLQPTRO + 1) .MOD. LCLQSIZ
- # E'E HEXDMP.(0,1,0,LOCALDEV)
-
- O'R TESTIO.(LOCALDEV(1)) .NE. 0
- ; this is for all of the other times through when io is done
- LOCALDEV(1) = -1 ; clear io flag
- E'E TPUTCH.(LCLCHQ(LCLQPTRO), LOCALDEV)
- LCLQPTRO = (LCLQPTRO + 1) .MOD. LCLQSIZ
- # E'E HEXDMP.(0,1,0,LOCALDEV)
- E'L
- E'L
-
- ; ditto
- W'R RMTQPTRI .NE. RMTQPTRO
- # E'E HEXDMP.(1,2,1,RMTDEV)
- W'R RMTDEV(1) .E. -1
- ; this is for the first time through
- E'E TPUTCH.(RMTCHQ(RMTQPTRO), RMTDEV)
- RMTQPTRO = (RMTQPTRO + 1) .MOD. RMTQSIZ
- # E'E HEXDMP.(1,2,1,RMTDEV)
-
- O'R TESTIO.(RMTDEV(1)) .NE. 0
- ; this is for all of the other times through when io is done
- RMTDEV(1) = -1 ; clear io flag
- E'E TPUTCH.(RMTCHQ(RMTQPTRO), RMTDEV)
- RMTQPTRO = (RMTQPTRO + 1) .MOD. RMTQSIZ
- # E'E HEXDMP.(1,2,1,RMTDEV)
- E'L
- E'L
-
- F'R
-
- DONE E'E OPAQUE.
- E'E TYPE.(0,0)
- F'N
- E'N
- <<< KERMIT.SCOPY >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;;;;;;;;;; SCOPY ;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SCOPY.(XFROM,I,XTO,J)
-
- I'R XFROM(1),XTO(1),I,J,K1,K2
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- K2=J
- K1=I
-
- W'E (XFROM(K1).NE.EOS)
- XTO(K2)=XFROM(K1)
- K2=K2+1
- K1=K1+1
- E'W
-
- XTO(K2)=EOS
- F'N
- E'N
- <<< KERMIT.SDATA >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;;;;;; SDATA ;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SDATA.(X)
-
- ; sends a data packet to other KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R X,NUM,LEN,STATUS,TNUM,TV1
- I'R RECKPT(100) ; packet to get the ack back in
- I'R LCLSTATE ; temp for returned state
-
- # E'E TYPMSG.($ IN SDATA !$)
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA
- E'E CLOSTEXT.(FD)
- T'O GETOUT
- O'E
- NUMTRY=NUMTRY+1
- E'L
-
- TNUM=N
- TV1=BIGD
-
- E'E SPACK.(TV1,TNUM,SIZE,PACKET) ;send that data packet
-
- STATUS=RPACK.(LEN,NUM,RECPKT) ;get the reply
-
- E'E DODOT. ; tell all if ok
-
- # E'E TYPOUT.(2,'A000'.LOR.STATUS)
- # E'E TYPEMSG.($ got dis status!$)
-
- ; the next statements is to make sure we are not one packet
- ; ahead of other KERMIT, it will happen if other KERMIT send a NAK
- ; (due to time-out detection feature) before we send the first
- ; SINIT packet
-
- W'R ((STATUS.EQ.BIGY).AND.(N.EQ.(NUM+1)))
- STATUS=RPACK.(LEN,NUM,RECKPT)
- E'L
-
- W'R (STATUS.EQ.BIGN) ;we got a NAK
- W'R (N.NE.(NUM-1))
- LCLSTATE=STATE ;to the right sequence #, tyr
- T'O GETOUT
- E'L
-
- O'R(STATUS.EQ.BIGY) ;we got a ACK
- W'R (N.NE.NUM)
- LCLSTATE=STATE ;but, it was for the last pac
- T'O GETOUT
- E'L
-
- NUMTRY=0
- N=(N+1).MOD.64 ;increment frame sequence num
- SIZE=BUFILL.(PACKET) ;fill up more data onto buffe
- W'R (SIZE.EQ.EOF) ;we got EOF on the sending
- LCLSTATE=BIGZ ;disk file, change state so t
- T'O GETOUT ;we can sent ane EOF packet
- E'L
-
- LCLSTATE=BIGD ;we send the DATA packet, sen
- T'O GETOUT
-
- O'R(STATUS.EQ.BAD) ;we got a checksum error
- LCLSTATE=STATE ;try it again
- T'O GETOUT
-
- O'E
- LCLSTATE=BIGA ;we got unknown packet type o
- E'E CLOSTEXT.(FD)
- T'O GETOUT
-
- E'L ;an error type packet
- GETOUT C'E
- # E'E TYPOUT.(2,'A000'.LOR. LCLSTATE)
- # E'E TYPEMSG.($ rdata exit state!$)
-
- F'N LCLSTATE
- E'N
- <<< KERMIT.SENDSW >>>
- ; 16 jly 5 esj converted
- ;;;;;;;;;;; SENDSW ;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SENDSW.(X)
-
- ; send this group of files
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- G'L XNEW,XCOUNT,XEOF
-
- I'R SDATA,SFILE,SEOF,SINIT,SBREAK
- I'R TV1,TV2,TV3,TV4
-
- STATE=BIGS
- XNEW=YES
- XCOUNT=1
- XEOF=NO
- N=0
- NUMTRY=0
- STATUS=YES
-
- W'E (STATUS.EQ.YES)
- # E'E TYPOUT.(2,'A000'.LOR.STATE)
- # E'E TYPEMSG.($ is current state!$)
-
- W'R (STATE.EQ.BIGD) ;send a data packet
- STATE=SDATA.(X)
-
- O'R (STATE.EQ.BIGF) ;send a file header
- STATE=SFILE.(X)
-
- O'R (STATE.EQ.BIGZ) ;send a EOF header
- STATE=SEOF.(X)
-
- O'R (STATE.EQ.BIGS) ;send a SINIT packe
- STATE=SINIT.(X)
-
- O'R (STATE.EQ.BIGB) ;send a BREAK packe
- STATE=SBREAK.(X)
-
- O'R (STATE.EQ.BIGC)
- LCLSTAT=YES ;file transfer comp
- B'K
-
- O'R (STATE.EQ.BIGA) ;file transfer fail
- LCLSTAT=NO
- TV1=BIGE
- TV2=N
- TV3=0
- TV4=0
- E'E SPACK.(TV1,TV2,TV3,TV4) ;send a ERROR packet
- B'K
-
- O'E
- STATUS=NO
- LCLSTAT=NO ;file transfer failu
- E'L
- E'W
- F'N LCLSTAT
- E'N
- <<< KERMIT.SEOF >>>
- ; 6 aug 85 esj restored send @file support
- ; 19 jly 85 esj removed send @file support
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;;;; SEOF ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SEOF.(X)
-
- ; send an EOF packet to the other KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R NUM,LEN,STATUS,LCLSTATE,TNUM
- I'R TPNAME(132),AONE,BONE,TV1,TV2,TV3
- I'R XREAD
- G'L IFD(*),IFDFLG
-
- XREAD=0
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max. # of re-try, give up
- E'E CLOSTEXT.(FD)
-
- O'E
- NUMTRY=NUMTRY+1
- AONE=1
- BONE=1
- TNUM=N
- TV1=BIGZ
- TV2=0
- TV3=0
- E'E SPACK.(TV1,TNUM,TV2,TV3) ;send an EOF packet to other KE
- STATUS=RPACK.(LEN,NUM,RECPKT) ;what is its reply ??
-
- W'R (STATUS.EQ.BIGN) ;we got an NAK
-
- LCLSTATE=STATE
- F'N LCLSTATE
-
- O'R (STATUS.EQ.BIGY) ;we got a ACK
- W'R (N.NE.NUM)
- LCLSTATE=STATE ;but it was for the last packet
-
- O'E
- N=(N+1).MOD.64
- NUMTRY=0
- E'E CLOSTEXT.(FD) ;close the sending disk file ch
-
- ; are we sending multiple files?
- W'R IFDFLG .E. YES
- R'T
- ; yes, get the next file
- E'E NEXTFILE.(IFD, TPNAME)
- W'R TPNAME .E. 0
- ; if at eof, close up shop
- LCLSTATE = BIGB
- B'K
-
- O'E
- ; go for next file
- LCLSTATE = BIGF
- STATUS = OPENTEXT.(TPNAME,$RD$, $CV$, FD)
-
- W'R (STATUS.NE.0) ;file exist ??
- ; no, say so and try again
- E'E TYPOUT.(TPNAME-1,TPNAME(1))
- E:E TYPEMSG.($ <--- Source file does not exist!$)
- E'E CLOSTEXT.(FD)
- LCLSTATE = BIGB
-
- O'E
- ; yes, all ok, convert the filename to
- ; kermit packet format, being careful to not
- ; include the ! terminator
- E'E CHTOIN.(TPNAME(1), FILNAME, TPNAME-1)
- B'K
-
- E'L
- E'L
- F'R
- O'E
- ; no more files, close up shop
- LCLSTATE = BIGB
-
- E'L
-
- E'L
-
- O'R (STATUS.EQ.BAD) ;there was a checksum error
- LCLSTATE=STATE ;try it again
-
- O'E
- LCLSTATE=BIGA ;we got an unexpected packet
- E'E CLOSTEXT.(FD)
- ;or error packet, abort
- ;transfer mode
- E'L
- E'L
- F'N LCLSTATE
- E'N
- <<< KERMIT.SETCOOK >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;; SETCOOK ;;;
- E'F
- E'O SETCOOK.(CH,FNAME)
-
- ; a noop for cgos. maybe replace with a call to transpare/opaque
- F'N
- E'N
- <<< KERMIT.SETPORT >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;; SETPORT ;;;;;;;;;;;;;;;;;;;;;;;
- E'F
- E'O SETPORT.(CH,FNAME)
-
- ; this routine would normally enable a user to select which
- ; port to used for remote file transfer, but it will not
- ; be implemented in the CGOS system. This routine is a nop until it
- ; can be used for setting the proper port configuration such as
- ; baud rate, parity, xon/xoff,enq/ack, stop bits, bpc etc
-
- F'N
- E'N
- <<< KERMIT.SETRAW >>>
- ; 16 jly 85 esj converted
- ;;;;;;;; SETRAW ;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F
- E'O SETRAW.(CH,FNAME)
-
- ; this is a noop for cgos.
-
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
-
- F'N
- E'N
- <<< KERMIT.SFILE >>>
- ; 16 jly 85 esj converted
- ;------------------------------------------< sfile >----------------------
- E'F A:S(NWLS)
- E'O SFILE.(X)
- ;-------------------------------------------------------------------------
- ;
- ; Purpose
- ; send the filename to other KERMIT
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Insert
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- ; Globals
- G'L XNEW,XCOUNT,XEOF,DODOTCT
-
- ; Locals
- I'R NUM,LEN,X,TNUM,LCLSTATE,STATUS
- I'R TV1,ALIN(132),AONE,BONE
-
- ;----------------------< start of code >----------------------------
-
- AONE=1
- BONE=1
- E'E SCOPY.(FILNAME,0,ALIN,0)
-
- W'R (HOSTON.EQ.NO)
- DODOTCT = 0
- E'E TYPE.(0,0)
- E'E TYPMSG.($Sending !$) ;we are in local mode dis
- E'E PUTLIN.(ALIN,LOCALDEV) ;the filename being send
- E'E TYPE.(0,0)
- E'L
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max. # of re-try
- F'N LCLSTATE ;gives up
- O'E
- NUMTRY=NUMTRY+1 ;try it one more time
- E'L
-
- LEN=0
- W'E (FILNAME(LEN).NE.EOS) ;determine the length of f
- LEN=LEN+1
- E'W
-
- TNUM=N
- TV1=BIGF
- E'E SPACK.(TV1,TNUM,LEN,FILNAME) ;send filename to other KE
- STATUS=RPACK.(LEN,NUM,RECPKT)
-
- W'R (STATUS.EQ.BIGN) ;we got a NAK
- W'R (N.NE.(NUM-1))
- LCLSTATE=STATE
- F'N LCLSTATE
- E'L
-
- O'R (STATUS.EQ.BIGY) ;we got a ACK
- W'R (N.NE.NUM)
- LCLSTATE=STATE
- F'N LCLSTATE
- E'L
- NUMTRY=0
- N=(N+1).MOD.64
- XNEW=YES
- XCOUNT=1
- XEOF=NO
- SIZE=BUFILL.(PACKET) ;fill up a buffer full of b
- LCLSTATE=BIGD ;change state to sent data
- F'N LCLSTATE
-
- O'R (STATUS.EQ.BAD) ;we got a checksum error
- LCLSTATE=STATE
- F'N LCLSTATE
- O'E
- LCLSTATE=BIGA ;we got an error or unexpec
- F'N LCLSTATE ;packet type
- E'L
- F'N LCLSTATE
- E'N
- <<< KERMIT.SHELP >>>
- ; 18 aug 85 esj replaced s.e.fm.error.uil with kerdef
- ; 31 jly 85 esj created
- ;---------------------------------------< shelp >---------------------------
- E'F A:S(NWLS)
- E'O SHELP.
- ;---------------------------------------------------------------------------
- ;
- ; Purpose
- ; Print out the help file for kermit.
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Globals
- ; none
-
- ; Inserts
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- /INCLUDE SYM.EQU.FM.OPEN
- /INCLUDE SYM.EQU.FM.BASIC
- /INCLUDE SYM.EQU.FM.READ
-
- ; Local static
- V'S HELPNAME = 31,$=SYSNEWS.CVCOMMAND.&BCD.KERMIT!$
-
- V'S TXTSPEC = 03,
- 1 %CATLOG,%%SEARCH,
- 1 %FORMAT , %%TEXT,
- 1 %RTNERR
-
- V'S RDSPC = 02,
- 1 %RTNERR,
- 1 %RETURN,1,
- 1 %%BYTCNT
-
-
- V'S CLOSPC = 1,
- 1 %RTNERR
-
-
- ; Local dynamic
- I'R CH ; channel holder
- I'R LINE(100) ; line buffer
- I'R OTSPC(9) ;
- I'R STATUS(1) ; FM error code
-
-
- ;----------------------------------< start of code >------------------------
-
- * Set to no error
- STATUS = STATUS(1) = FM%NOERR
-
- ; call the fm and try to open the help file
- E'E F&OPEN.(%OREAD ,
- 1 %IDFILNM ,
- 1 HELPNAME ,
- 1 TXTSPEC ,
- 1 CH ,
- 1 OTSPC ,
- 1 STATUS )
-
- # E'E HEXDMP.(1,1,1,STATUS)
-
- ; type out contents of file
- W'R STATUS .E. FM%NOERR
- ; if open status is ok, print till eof
- R'T
- E'E F&READ.(CH ,
- 1 1 ,
- 1 LINE ,
- 1 RDSPC ,
- 1 OTSPC ,
- 1 STATUS )
-
- # E'E HEXDMP.(1,1,1,STATUS)
- W'R STATUS .NE. FM%NOERR, B'K
-
- E'E TYPE.(OTSPC(3),LINE)
- F'R
- E'L
-
- E'E F&CLOSE.(CH, CLOSPC, STATUS)
-
- F'N STATUS
- E'N
- <<< KERMIT.SINIT >>>
- ; 18 jly 85 esj removed send @filename support
- ; 16 jly 85 esj converted
- ;;;;;;;;;;; SINIT ;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SINIT.(X)
-
- ; send an initial packet for the first connection
- ; state what my parameters are
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R NUM,LEN,STATUS,LCLSTATE,TNUM
- I'R AONE,BONE,TV1,TV2
-
-
- W'R (NUMTRY.GT.MAXTRY)
- LCLSTATE=BIGA ;exceeded max # of re-try , give up
-
- O'E
- NUMTRY=NUMTRY+1 ;try it again
-
-
- AONE=1
- BONE=1
- E'E SPAR.(PACKET) ;get my requirement parameters
- # E'E HEXDMP.(1,11,1,PACKET)
- TNUM=N
- TV1=BIGS
- TV2=6
- E'E SPACK.(TV1,TNUM,TV2,PACKET) ;send my parameters requiremen
- STATUS=RPACK.(LEN,NUM,RECPKT) ;what was the reply ??
-
- # E'E TYPOUT.(2,'A000'.LOR.STATUS)
- # E'E TYPEMSG.($ got dis status!$)
-
- W'R (STATUS.EQ.BIGN) ;NAK it
- LCLSTATE=STATE ;try it again
-
- O'R (STATUS.EQ.BIGY) ;ACK it
- W'R (N.NE.NUM) ;but it was for the previous p
- LCLSTATE=STATE ;re-try it again
-
- O'E
- E'E RPAR.(RECPKT) ;get the packet reqirement of
- ;other KERMIT if provided
- NUMTRY=0
- N=((N+1).MOD.64)
- LCLSTATE = BIGF
- E'L
-
- O'R (STATUS.EQ.BAD) ;checksum error detected
- LCLSTATE=STATE ;try it again
-
- O'E
- LCLSTATE=BIGA
-
- E'L
- E'L
-
- F'N LCLSTATE
- E'N
- <<< KERMIT.SPACK >>>
- ; 07 aug 85 dg call TPUTCH with rmtdev - nuke CH
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;; SPACK ;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SPACK.(XTYPE,NUM,LEN,XDATA)
-
- ; send this packet to the remote KERMIT
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R XTYPE,XDATA(1),NUM,LEN
- I'R TV1,TV2,TV3
- I'R I,COUNT,CHKSUM,BUFFER(132)
-
-
- ;------------------------------< real code >----------------------------
-
- I=0 ;out on, start with the first byte
-
- W'E (I.LE.PAD) ;send out padchar if need
- E'E TPUTCH.(PADCHAR,RMTDEV)
- I=I+1
- E'W
- ; ;build up the packet
- COUNT=0
-
- BUFFER(COUNT)=SOH
- COUNT=COUNT+1
-
- CHKSUM=TOCHAR.(LEN+3)
- BUFFER(COUNT)=TOCHAR.(LEN+3)
- COUNT=COUNT+1
-
- CHKSUM=CHKSUM+TOCHAR.(NUM)
- BUFFER(COUNT)=TOCHAR.(NUM)
- COUNT=COUNT+1
-
- CHKSUM=CHKSUM+XTYPE
- BUFFER(COUNT)=XTYPE
- COUNT=COUNT+1
-
- T'H L1 FOR I=0, 1, I .GE. LEN ;copy the content of packet informa
- BUFFER(COUNT)=XDATA(I) ;calculate the checksum
- COUNT=COUNT+1
- CHKSUM=CHKSUM+XDATA(I)
- L1 C:E
-
- TV1=CHKSUM.LAND.192
- TV2=TV1/64
- TV3=TV2+CHKSUM
- CHKSUM=TV3.LAND.63
-
- BUFFER(COUNT)=TOCHAR.(CHKSUM)
- COUNT=COUNT+1
-
- BUFFER(COUNT)=EOL
- BUFFER(COUNT+1)=EOS
- * E'E HEXDMPP.(1,COUNT+2,1,BUFFER)
-
- COUNT=0
-
- W'E (BUFFER(COUNT).NE.EOS) ;send out the packet
- E'E TPUTCH.(BUFFER(COUNT),RMTDEV)
- COUNT=COUNT+1
- E'W
-
- F'N GOOD
-
- E'N
- <<< KERMIT.SPAR >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;;;;;;;;; SPAR ;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SPAR.(XDATA)
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- I'R XZERO
- I'R XDATA(5)
-
- XZERO=0
- XDATA(0)=TOCHAR.(PAKSIZ)
- XDATA(1)=TOCHAR.(XZERO)
- XDATA(2)=TOCHAR.(XZERO)
- XDATA(3)=CTL.(XZERO)
- XDATA(4)=TOCHAR.(MYEOL)
- XDATA(5)=MYQUOTE
-
- F'N
- E'N
- <<< KERMIT.SQUIT >>>
- ; 16 jly 85 esj converted
- ;;;;;;;;;;;;; SQUIT ;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O SQUIT.
-
- ; exit from the CVkermit program
-
- E'E NEXTCOMM.
- F'N
- E'N
- <<< KERMIT.SRECEIVE >>>
- ; 16 jly 84 esj; converted
- ;-------------------------------------< sreceive >--------------------------
- E'F A:S(NWLS)
- E'O SRECEIVE.
- ;----------------------------------------------------------------------------
- ;
- ; Purpose
- ; sets up TTY line before calling for RECSW routine
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Inserts
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- ; Globals
- ; none
-
- ; Locals
- I'R LOGTTY(132),STATUS,X,BELL
-
- ;---------------------------< start of code >-------------------------------
-
- BELL=7
-
- W'R (HOSTON.EQ.YES)
- E'E SETRAW.(RMTDEV,LOGTTY) ;put this TTY into RAW mode
-
- STATUS=RECSW.(X)
-
- E'E SETCOOK.(RMTDEV,LOGTTY) ;put this TTY back into COOK mod
-
- O'E
- E'E SETRAW.(RMTDEV,RMTTTY) ;put this TTY into RAW mode
-
- STATUS=RECSW.(X)
-
- E'E SETCOOK.(RMTDEV,RMTTTY) ;put TTY back into COOK mode
-
- E'E TYPE.(0,0)
-
- W'R (STATUS.EQ.YES)
- E:E TYPEMSG.($File transfer COMPLETED!$)
- O'E
- E:E TYPEMSG.($File transfer FAILED!$)
- E'L
- E'L
- F'N
- E'N
- <<< KERMIT.SSEND >>>
- ; 6 aug 85 esj add support for @filename
- ; 23 jly 85 esj fixing filename problems
- * 19-Jul-85 LEC; tpl conversion, first pass
- ;;;;;; SSEND ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E:F A:S (NWLS,STKARG)
- E'O SSEND.
-
- ; setting up remote line and directory file before calling SENDSW
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- G:L CHAR
- G:L TPNAME(*)
- G'L IFD(*) ; file descriptor for file containing a list of
- ; files to be sent
- G'L IFDFLG ; yes = file names from ifd file/ no = only 1 file
- I'R STATUS
- I'R X,BELL
-
-
- BELL=7
-
- ; test for empty line
- E:E NXTCHAR.(1)
-
- W'R CHAR .E. 0
- E:E TYPEMSG.($Proper format is "SEND [@]FILENAME"!$)
- T'O BADOUT
- E'L
-
- ; restore the last char if not at eol
- E'E PREVCHAR.(1)
-
- W'R CHAR .E. $@$
- ; get the file name to send from our source file
- IFDFLG = YES
-
- ; trash the @ char before getting the filename
- E:E NXTCHAR.(1)
- E:E FMNAME.(TPNAME)
-
- STATUS = OPENTEXT.(TPNAME,$RD$, $CV$, IFD)
-
- W'R (STATUS.NE.0) ;file exist ??
- E'E TYPOUT.(TPNAME-1,TPNAME(1))
- E:E TYPEMSG.($ <--- Indirection source file does not exist!$)
- E'E CLOSTEXT.(IFD)
- T'O BADOUT
-
- O'E
- ; get the first file to read
- E'E NEXTFILE.(IFD, TPNAME)
- W'R TPNAME .E. 0, T'O BADOUT
- E'L
-
- O'E
- ; get the only file to read
- IFDFLG = NO
- E:E FMNAME.(TPNAME)
-
- E'L
-
- STATUS = OPENTEXT.(TPNAME,$RD$, $CV$, FD)
-
- W'R (STATUS.NE.0) ;file exist ??
- E'E TYPOUT.(TPNAME-1,TPNAME(1))
- E:E TYPEMSG.($ <--- Source file does not exist!$)
- E'E CLOSTEXT.(FD)
- O'E
-
- ; convert filename to kermit type string, being careful to not
- ; include the ! terminator
- E'E CHTOIN.(TPNAME(1), FILNAME, TPNAME-1)
-
- W'R (HOSTON.EQ.YES) ;we are running in Host mode
-
- E'E TYPE.(0,0)
- E'E TYPMSG.($File OK, Waiting !$)
- E'E TYPEINT.(DELAY)
- E'E TYPEMSG.($ seconds!$)
- E'E XDELAY.(DELAY)
- STATUS=SENDSW.(X) ;send the requested file
-
- O'E
-
- STATUS=SENDSW.(X) ;send the request fi
-
- E'L
-
- E'E TYPE.(0,0)
-
- W'R (STATUS.EQ.YES)
- E:E TYPEMSG.($file transfer COMPLETED!$)
- O'E
- E:E TYPEMSG.($file transfer FAILED!$)
- E'L
-
- E'L
-
- E'E CLOSTEXT.(FD)
- BADOUT C'E
- F'N
- E'N
- <<< KERMIT.SSET >>>
- ; 16 jly 85 pcc allow the port attached by select line start with non-alpha
- ; characters.
- ; 26 jly 85 esj attach to port on set line <XXXX> command
- ; 24 jly 85 esj fix setup port selection
- * 16-Jul-85 LEC; tpl conversion, parsing.
- ;----------------------------------------< sset >----------------------------
- E:F
- E'O SSET.(X)
- ;----------------------------------------------------------------------------
- ;
- ; Purpose
- ; parse and set various selectable parameters
-
- ; Input
- ; none
-
- ; Output
- ; none
-
- ; Inserts
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- ; Globals
- G:L CHAR
-
- ; Local storage
- I:R OPTION(4),KEYWORD(4),X
- I'R UNITNUM(1)
-
- ;---------------------------< start of code >-------------------------------
- ; grab option to set
- E:E IDENT.(OPTION)
-
- W'R COMPNAM.(OPTION,$BAUD $).E.0
- E:E TYPEMSG.($Baud rate setting not supported!$)
-
- O'R COMPNAM.(OPTION,$DELAY $).E.0
- W'R (HOSTON.EQ.NO)
- E:E TYPEMSG.($Delay setting not valid in Local Host mode!$)
- F'N
- E'L
- E:E INT.(X)
- W'R (X.LT.0)
- E:E TYPEMSG.($Invalid delay setting!$)
- F'N
- O'R(X.GT.30)
- E:E TYPEMSG.($Delay setting too long!$)
- E:E TYPEMSG.($defaulted to 30 seconds!$)
- DELAY=30
- F'N
- O'E
- DELAY=X
- F'N
- E'L
- O'R COMPNAM.(OPTION,$PARITY $).E.0
- E:E TYPEMSG.($Parity setting not supported.!$)
-
- O'R COMPNAM.(OPTION,$IBM $).E.0 ;set IBM
- W'R (HOSTON.EQ.YES)
- E:E TYPEMSG.($SET IBM ON/OFF not supported in!$)
- E:E TYPEMSG.($Remote Host mode!$)
- F'N
- O:E
- E:E IDENT.(KEYWORD)
- W'R COMPNAM.(KEYWORD,$ON $).E.0
- IBMON=YES ;set IBM flag ON
- O'R COMPNAM.(KEYWORD,$OFF $).E.0
- IBMON=NO ;set IBM flag OFF
- O'E
- E:E TYPEMSG.($Invalid SET IBM mode selected!$)
- F'N
- E'L
- E:L
- O'R COMPNAM.(OPTION,$ESCAPE $).E.0 ;set escape
- W'R (HOSTON.EQ.YES)
- E:E TYPEMSG.($Escape setting not valid in!$)
- E:E TYPEMSG.($Remote Host mode!$)
- F'N
- O:E
- E:E INT.(X)
- W'R ((X.GT.0).AND.(X.LT.32))
- ESCHAR=X
- O'E
- E:E TYPEMSG.($Escape character must be between 0 & 32!$)
- F'N
- E'L
- E:L
- O'R COMPNAM.(OPTION,$LINE $).E.0 ;set remote line
-
- W'R (SPORT.EQ.YES) ;is set line supported ??
- I = 0
- ; fill keyword with blanks to set things up
- E:E FILLCHRT.(8,$ $,KEYWORD,0)
-
- ; grab next 8 char. can't use ident because any char is
- ; legal for a device name!
- W:E (CHAR.NE.0) .AND. (CHAR.NE.$ $) .AND. (I.L.8)
- E:E STCHRT.(CHAR,KEYWORD,I)
- E:E NXTCHAR.(0)
- I .INCR. 1
- E:W
-
- W:R CHAR .E. $ $, E:E NXTCHAR.(1)
- W:R COMPNAM.(KEYWORD,$COMDEV $).E.0
- RMTDEV = $SD$
- HOSTON = YES
- E'E DETACH.($KM$)
- O:E
- ; connect to the port indicated by the word following LINE
- # E'E HEXDMP.(0,4,0,KEYWORD)
- E'E UNBYUNM.( UNITNUM(1), KEYWORD)
- W'R UNITNUM(1) .E. -1
- E'E TYPOUT.(4,KEYWORD)
- E'E TYPEMSG.($ does not exist.!$)
- O'E
- ; if the port exists, attach to it.
- # E'E HEXDMP.(0,4,0,KEYWORD)
- UNITNUM = -1
- # E'E HEXDMP.(1,2,1,UNITNUM)
- ; detach from kermit device before attaching another
- E'E DETACH.($KM$)
-
- ; now attach to the device
- W'R ATTACH.($KM$, UNITNUM) .E. 1
- RMTDEV = $KM$
- HOSTON = NO
- E'E TYPOUT.(4,KEYWORD)
- E'E TYPEMSG.($ is connected.!$)
- O'E
- E'E TYPOUT.(4,KEYWORD)
- E'E TYPEMSG.($ is not available for connection.!$)
- # E'E HEXDMP.(0,4,0,KEYWORD)
- E'L
- E'L
- E:L
- F'N
- O'E
- E:E TYPEMSG.($SET remote line is not supported!$)
- F'N
- E'L
-
- O'R COMPNAM.(OPTION,$PROMPT $).E.0
- W'R (HOSTON.EQ.YES)
- E:E TYPEMSG.($SET IBM PROMPT not valid!$)
- E:E TYPEMSG.($In Remote Host mode!$)
- F'N
- O:E
- E:E INT.(X)
- W'R ((X.EQ.EOL).OR.(X.EQ.SOH))
- E:E TYPEMSG.($Invalid; in conflict with EOL or SOH!$)
- F'N
- O'E
- W'R ((X.GT.0).AND.(X.LT.32))
- PROMPT=X
- E:L
- E'L
- E:L
- O'R COMPNAM.(OPTION,$PACKET $).E.0
- E:E INT.(X)
- W'R ((X.GT.30).AND.(X.LT.95))
- PAKSIZ=X
- F'N
- O'E
- E:E TYPEMSG.($Invalid Packet size specifiecd!$)
- F'N
- E'L
- O'R COMPNAM.(OPTION,$SOH $).E.0
- E:E INT.(X)
- W'R (HOSTON.EQ.YES)
- W'R (X.EQ.EOL)
- E:E TYPEMSG.($Invalid; in conflict with EOL!$)
- F'N
- O'E
- W'R ((X.GT.0).AND.(X.LT.32))
- SOH=X
- F'N
- O'E
- E:E TYPEMSG.($Invalid; SOH must be between 0 & 32!$)
- F'N
- E'L
- E'L
- O'E
- W'R ((X.EQ.EOL).OR.(X.EQ.PROMPT))
- E:E TYPEMSG.($Invalid; in conflict with EOL!$)
- E:E TYPEMSG.($or IBM prompt!$)
- F'N
- O'E
- W'R ((X.GT.0).AND.(X.LT.32))
- SOH=X
- F'N
- O'E
- E:E TYPEMSG.($Invalid; SOH must be between!$)
- E:E TYPEMSG.($0 & 32!$)
- F'N
- E'L
- E'L
- E'L
- O'R COMPNAM.(OPTION,$QUOTE $).E.0
- E:E INT.(X)
- W'R ((X.GT.32).AND.(X.LT.127))
- MYQUOTE=X
- F'N
- O'E
- E:E TYPEMSG.($QUOTE character must be between!$)
- E:E TYPEMSG.($32 & 127!$)
- F'N
- E'L
- O'E
- E:E TYPEMSG.($Invalid SET parameter(s) detected!$)
- F'N
- E'L
- F'N
- E:N
- <<< KERMIT.SSTATUS >>>
- ; 23 jly 85 esj added display of eol
- ; 20 jly 85 lec converted
- ;;;;;;;;; SSTATUS ;;;;;;;;;;;;;;;;;;;;;;;
- E:F A:S (NWLS)
- E'O SSTATUS.
-
- ; output the status and values of variables
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERCOM
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- I'R I
-
- W'R (HOSTON.EQ.YES) ;we are running in remote host mode
- E:E TYPEMSG.($Remote Host KERMIT mode in effect!$)
- E:E TYPEINT.(DELAY)
- E:E TYPEMSG.($ = DELAY in seconds!$)
- E:E TYPEINT.(MYEOL)
- E:E TYPEMSG.($ = MYEOL!$)
- E:E TYPEINT.(EOL)
- E:E TYPEMSG.($ = EOL!$)
- E:E TYPEINT.(PAKSIZ)
- E:E TYPEMSG.($ = PAKSIZ!$)
- E:E TYPEINT.(MYQUOTE)
- E:E TYPEMSG.($ = MYQUOTE!$)
- E:E TYPEINT.(SOH)
- E:E TYPEMSG.($ = SOH!$)
- W'R (STATE.EQ.BIGC)
- E:E TYPEMSG.($File transfer state = C!$)
- O'E
- E:E TYPEMSG.($File transfer state = A!$)
- E'L
- O'E
- E:E TYPEINT.(MYEOL)
- E:E TYPEMSG.($ = MYEOL!$)
- E:E TYPEINT.(ESCHAR)
- E:E TYPEMSG.($ = ESCAPE Char!$)
- W'R (IBMON.EQ.YES)
- E:E TYPEMSG.($IBM flag = ON!$)
- E:E TYPEINT.(PROMPT)
- E:E TYPEMSG.($ = IBM PROMPT!$)
- O'E
- E:E TYPEMSG.($IBM flag = OFF!$)
- E'L
- E:E TYPEINT.(PAKSIZ)
- E:E TYPEMSG.($ = PACKET size!$)
-
- E:E TYPEINT.(MYQUOTE)
- E:E TYPEMSG.($ = MYQUOTE!$)
- E:E TYPEINT.(SOH)
- E:E TYPEMSG.($ = SOH!$)
- E:E TYPEMSG.($Remote TTY line used is ??!$)
- W'R (STATE.EQ.BIGC)
- E:E TYPEMSG.($File transfer state = C!$)
- O'E
- E:E TYPEMSG.($File transfer state = A!$)
- E'L
- E'L
- F'N
- E:N
- <<< KERMIT.TEXT-FILE-IO >>>
- ; 18 aug 85 esj replaces s.e.fm.error.uil with kerdef
- * 18 jly 85 ESJ CREATED FOR kermit
- *
- *----------------------------- text-file-io -------------------------
- E:F A:S(NWLS , STKARG)
- *-----------------------------------------------------------------------
- *
- * PURPOSE
- *
- * INPUT
- I'R FD(*) ; file descriptor block
- *
- * OUTPUT
- *)
- *
- * GLOBALS DEFINITIONS
- * none
- *
- * LOCAL DEFINITIONS
- I'R NEWNAME(42) ; dest name field
- I'R PACKNAME(42) ; temp for packed filename
- I'R OPENMODE ; open mode temp
- I'R TEMPMODE ; open mode temp
- I'R OTSPC(9) ;
- I'R STATUS(1) ; FM error code
- I'R WRSPEC(3) ; inspecs field for write call
-
-
- * SUBROUTINES CALLED
- *
- * INSERTS
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
- /INCLUDE SYM.EQU.FM.OPEN
- /INCLUDE SYM.EQU.FM.BASIC
- /INCLUDE SYM.EQU.FM.READ
-
- *--- put equates for the FD block here till ready to move to sym file---
-
- EQU FD&CHAN = 0 ; channel number of the file once it's
- ; open
-
- EQU FD&MAX = 1 ; maximum length of the text record which
- ; can be handled by this FD. It is also
- ; the size of the FD&TXTB field.
-
- EQU FD&NDX = 2 ; index for next char to be read from TXTB
-
- EQU FD&MODE = 3 ; mode of how the file was opened
-
- EQU FD&LNPOS= 4 ; number of current line being read. 0 based
-
- EQU FD&TXTC = 5 ; text count. The length of the text record
- ; currently in this FD
-
- EQU FD&TXTB = FD&TXTC+1 ; text buffer
-
- *-----------------------------------------------------------------------
- *
- * STATIC DATA INITIALIZATION
- V'S TXTSPEC = 03,
- 1 %CATLOG,%%SEARCH,
- 1 %FORMAT , %%TEXT,
- 1 %RTNERR
-
- V'S BCDNAME = 4,$&BCD$
- *
- * RESTRICTIONS
- *
- * ERROR INDICATIONS
- *
- * METHOD
- *
- *
- *---------------------------- START OF CODE ----------------------------
- * HOW TO USE
- * opentext is part of a simplified interface for manipulating
- * text files with the new file manager. opentext is used to
- * open a text file for stream io.
- * opentext takes four arguments:
- * 1) FD is a buffer that contains information about the file and
- * the record being manipulated. the information in FD is to be
- * hidden from the user so that information can be added,deleted
- * or changed without the need to support existing structures.
- * The size of FD is defined by FD&SIZE. The buffer will need to
- * be created by an ALLOC call because the buffer is larger than a
- * local data section.
- * 2) FILENAME is a string in kermit or cv format. opentext will
- * make a copy of the file name and add an &bcd level to the name
- * and stick an ! on the end, if needed converting the file name
- * to a proper text file name.
- * 3) TEXTMODE is a two character descripter for the open mode for
- * a text file. The only modes supported are, RD for read,
- * MO for modify, and SU for supercede.
- *
- * 4) NAMETYPE defines the type of string in filename. CV is a cv type
- * of string. KM is a kermit type of string.
- *
- E'O OPENTEXT.( FILENAME, TEXTMODE, NAMETYPE, FD)
-
- # E'E TYPE.(2,NAMETYPE)
- ; convert filename to &bcd type and put ! on end
- W'R NAMETYPE .E. $KM$
- # E'E HEXDMPP.(1,41,1,FILENAME)
- E'E PACK.(FILENAME, PACKNAME )
- # E'E HEXDMP.(2,42,2,PACKNAME)
- E'E FMEXPNM.(PACKNAME,BCDNAME,NEWNAME)
- O'E
- E'E FMEXPNM.(FILENAME,BCDNAME,NEWNAME)
- E'L
-
-
- W'R LDCHRT.(NEWNAME(1),NEWNAME-1) .NE. $!$
- E'E STCHRT.($!$,NEWNAME(1),NEWNAME)
- NEWNAME(0) = NEWNAME(0) + 1
- E'L
-
- # E'E TYPEMSG.($THIS SHOULD BE THE &BCD NAME!$)
- # E'E HEXDMP.(0,NEWNAME,0,NEWNAME)
-
- ; convert textmode to open file mode
- ; convert char string to cv char type and lower case
- TEMPMODE = TEXTMODE .LOR. 'A0A0'
-
- # E'E HEXDMP.(TEMPMODE,TEMPMODE,TEMPMODE,TEMPMODE)
- W'R TEMPMODE .E. $rd$
- ; read mode
- OPENMODE = %OREAD
- *
- O'R TEMPMODE .E. $mo$
- ; modify mode
- OPENMODE = %OMODIFY
- *
- O'R TEMPMODE .E. $su$
- ; supercede mode
- OPENMODE = %OSUPR
-
- O'E
- ; force openmode error
- OPENMODE = -1
-
- E'L
- *
- * Set to no error
- STATUS = STATUS(1) = FM%NOERR
-
- ; call the fm and try to open
- E'E F&OPEN.(OPENMODE,
- 1 %IDFILNM,
- 1 NEWNAME ,
- 1 TXTSPEC ,
- 1 FD(FD&CHAN),
- 1 OTSPC ,
- 1 STATUS )
-
- # E'E HEXDMP.(1,1,1,STATUS)
- *
- FD(FD&NDX) = 0 ; make text buffer empty
- FD(FD&TXTC) = 0
- FD(FD&MODE) = OPENMODE ; set up access protection
- FD(FD&LNPOS) = 0
-
- F:N STATUS
-
-
- *------------ end of opentext -------------------------------------
- *------------ start of dgetch --------------------------------------
- * dgetch is part of a simplified interface for Manipulating
- * text files with the new file manager. dgetch is used to
- * read characters from a text file for stream io.
- * dgetch takes two arguments:
- * 1) CHAR is a single char from the file described in FD. The
- * character is in kermit format. When end of file is reached,
- * CHAR will equal -1. End of line is indicated by CR.
- * 2) FD is a buffer that contains information about the file and
- * the record being manipulated. the information in FD is to be
- * hidden from the user so that information can be added,deleted
- * or changed without the need to support existing structures.
- * The size of FD is defined by FD&SIZE. The buffer will need to
- * be created by an ALLOC call because the buffer is larger than a
- * local data section.
- *
- V'S RDSPC = 02,
- 1 %RTNERR,
- 1 %RETURN,1,
- 1 %%BYTCNT
-
- E'O DGETCH.(CHAR, FD)
-
- STATUS = STATUS(1) = 0
-
- ;if char index = 0 read in line and stick cr at end
- W'R FD(FD&NDX) .E. 0
-
- E'E F&READ.(FD(FD&CHAN),
- 1 1 ,
- 1 FD(FD&TXTB) ,
- 1 RDSPC ,
- 1 OTSPC ,
- 1 STATUS )
-
- W'R STATUS .GE. FM%NOERR
- FD(FD&TXTC) = OTSPC(3)
- E'E STBYTT.('8D', FD(FD&TXTB), FD(FD&TXTC))
- FD(FD&TXTC) = FD(FD&TXTC) + 1
- E'L
-
- E'L
-
- W'R STATUS .GE.FM%NOERR
- ; get a char from the input stream
- CHAR = LDBYTT.(FD(FD&TXTB), FD(FD&NDX)) .LAND. '7F'
-
- W'R CHAR .E. '000D'
- FD(FD&NDX) = 0
- FD(FD&LNPOS) = FD(FD&LNPOS) + 1
- O'E
- FD(FD&NDX) = FD(FD&NDX) + 1
- E'L
-
- O'R STATUS .E. UL%RDEOF
- ; if at eof set char = -1
- CHAR = -1
-
- E'L
-
- F'N STATUS
-
- *-------------- end of dgetch -----------------------------------------
- *-------------- start of dputch ---------------------------------------
- * dputch is part of a simplified interface for manipulating
- * text files with the new file manager. dputch is used to
- * write a stream of characters to a text file.
- * dputch takes two arguments:
- * 1) CHAR is a single char from the file described in FD. The
- * character is in kermit format. The end of line is indicated by
- * the symbol CR.
- * 1) FD is a buffer that contains information about the file and
- * the record being manipulated. the information in FD is to be
- * hidden from the user so that information can be added,deleted
- * or changed without the need to support existing structures.
- * The size of FD is defined by FD&SIZE. The buffer will need to
- * be created by an ALLOC call because the buffer is larger than a
- * local data section.
-
- E'O DPUTCH.(CHAR, FD)
-
- STATUS = 0
- # E'E HEXDMP.(0,0,0,CHAR)
- # E'E HEXDMP.(1,50,1,FD(FD&TXTC))
- W'R CHAR .NE. '000D'
- W'R CHAR .E. '000A' .AND. FD(FD&TXTC) .E. 0 , T:O EXITPCH
- FD(FD&NDX) = FD(FD&NDX) + 1
- W'R PACKLINE.((CHAR), FD(FD&TXTC)) .NE. -1, T:O EXITPCH
- E'L
- WRSPEC(0) = 2
- WRSPEC(1) = %RECLEN
- WRSPEC(2) = FD(FD&TXTC)
- WRSPEC(3) = %RTNERR
- E'E F&WRITE.(FD(FD&CHAN), 1, FD(FD&TXTB), WRSPEC, OTSPC, STATUS)
-
- FD(FD&TXTC) = FD(FD&NDX) = 0
- FD(FD&LNPOS) = FD(FD&LNPOS) + 1
-
- EXITPCH C'E
- F'N STATUS
-
-
- *-------------- end of dputch -----------------------------------------
- *-------------- start of closstrm -------------------------------------
- * closstrm is part of a simplified interface for manipulating
- * text files with the new file manager. closstrm is used to
- * close a text file used for stream io.
- * closstrm takes one argument:
- * 1) FD is a buffer that contains information about the file and
- * the record being manipulated. the information in FD is to be
- * hidden from the user so that information can be added,deleted
- * or changed without the need to support existing structures.
- * The size of FD is defined by FD&SIZE. The buffer will need to
- * be created by an ALLOC call because the buffer is larger than a
- * local data section.
- *
- V'S CLOSPC = 1,
- 1 %RTNERR
-
- E'O CLOSTEXT.(FD)
-
- # E'E TYPEMSG.($ CLOSSTRM!$)
- # E'E HEXDMP.(0,0,0,FD(FD&TXTC))
- W'R FD(FD&TXTC) .NE. 0
- ; the line buffer is not empty, so flush the line to disk
- E'E DPUTCH.('000D', FD)
- E'L
-
- E'E F&CLOSE.(FD(FD&CHAN),CLOSPC, STATUS)
-
- F'N STATUS
-
- *-------------- end of clostext -------------------------------------
- *
- E:N
- <<< KERMIT.TGETCH >>>
- ; 29 jly 85 esj added timeout support
- ; 17 jly 85 esj converted
- ;;;;;;;;;;; TGETCH ;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O TGETCH.(XCHAR,UNIT)
-
- ; PURPOSE
- ; get a CHAR from the TTY without echoing it
-
- ; INPUT
- ; none
-
- ; OUTPUT
- I'R XCHAR ; char output- char in lo byte
- I'R UNIT ; unit we expect input from
-
- ; LOCAL STORAGE
- I'R TYPE ; type of input from tis
- I'R COUNT ; count of char input from tis
- I'R CHBUF ; buffer of char input from tis
- I'R TISUNIT ; unit the input came from
-
- ; global
- G'L TIMEOUT(1)
- G'L LOCALDEV
- G'L HOSTON
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- # E'E TYPOUT.( 2,UNIT )
- # E'E TYPEMSG.($ <--- UNIT TO GET INPUT FROM!$ )
-
- R'T
-
- E'E INPUT.(TISUNIT, TYPE, COUNT, CHBUF)
-
- W'R HOSTON .E. NO .AND. TISUNIT .E. LOCALDEV
- ; we probably hung, so abort to rpack as a bad packet
- E'E LBLGO.(TIMEOUT)
- E'L
-
- U'L UNIT .E. TISUNIT
-
- # E'E TYPEHEX.(CHBUF)
-
- XCHAR = CHBUF .LAND. '7F'X
-
- F'N OK
- E'N
- <<< KERMIT.TOCHAR >>>
- ; 18 jly 85 esj converted
- ;;;;;;;;;;;; TOCHAR ;;;;;;;;;;;;;;;;;;;;;;C
- E'F
- E'O TOCHAR.(CH)
-
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- F'N (CH+BLANK)
- E'N
- <<< KERMIT.TPUTCH >>>
- ; 15-AUG-85 MVI: CHANGED NO IOFLAG VALUE FROM 0 TO -1.
- ; 07 AUG 85 DG IOFLAG IS PART OF UNIT
- ; 06 AUG 85 DG ADDED NO WAIT I/O SUPPORT
- ; 17 jly 85 esj converted
- ;;;;;;;;;;;;;; TPUTCH ;;;;;;;;;;;;;;;;;;;;;;;;
- E'F A:S(NWLS)
- E'O TPUTCH.(XCHAR, UNIT)
-
- ; PURPOSE
- ; output a char to the TTY line
-
- ; INPUT
- I'R XCHAR ; char output- char in lo byte
- I'R UNIT(1) ; UNIT(0) unit we want to send char to
- ; UNIT(1) I/O flag for the unit
-
- ; OUTPUT
- ; none
-
-
- ; LOCAL STORAGE
- I'R ARGLIST(2)
- I'R CHAR ; local char temp
-
- ;------------------------< start of executable code >-----------------------
-
- # E'E TYPE.(2,UNIT)
- # E'E HEXDMP.(0,0,0,XCHAR)
-
- ARGLIST(0) = 0
- ARGLIST(1) = 1
- ARGLIST(2) = 0
-
- CHAR = XCHAR .LSH. 8
-
- W'R UNIT(1) .NE. -1
- ; -1 means first time through for this unit
-
- W:R TESTIO.(UNIT(1)).E.0 ;I/O IN PROGRESS FROM LAST REQUEST
- E:E WAITIO.(UNIT(1)) ;WAIT FOR I/O TO FINISH
- E:L
- E'L
-
- UNIT(1) = CONTROL.( UNIT, ARGLIST, CHAR, '0001') ;NO WAIT I/O
-
- F'N
- E'N
- <<< KERMIT.UN&PACK >>>
- * 27-AUG-83 JDG
- *
- *------------------------------------------- ???????.UN&PACK ----------
- E:F A:S(NWLS , STKARG)
- *-----------------------------------------------------------------------
- *
- * PURPOSE
- *
- * PACKLINE: ADD CHAR TO AN ARRAY
- * EMPTLINE: UNPACK A CHAR FROM ARRAY CHARACTER INTO CHAR
- *
- * INPUT
- *
- * PACKLINE: CHAR: ELEMENT TO ADD TO ARRAY
- * ARRAY: ARRAY TO STUFF CHAR INTO
- * EMPTLINE: ARRAY: ARRAY FROM WHICH TO DRAW CHAR
- *
- * OUTPUT
- *
- * PACKLINE: UPDATED ARRAY
- * F:N TRUE ==> ARRAY FULL
- * F:N FALSE==> ARRAY NOT FULL
- * EMPTLINE: CHAR FROM ARRAY,UPDATED ARRAY
- * F:N TRUE ==> ARRAY EMPTY
- * F:N FALSE==> ARRAY NOT EMPTY
- *
- * LOCAL DEFINITIONS
- *
- I:R CHAR ; contains char to be put into array
- ; char format can be the same as fig-forth
- ; char is in lower byte of word '00cc' where
- ; cc is the hex code for a char
- ; or the chat format can be that of cgos where
- ; the char is in the high order byte and has
- ; the '80' bit turned on
-
- D:N ARRAY(81) ; array contains the string of packed chars
- ; the format of array is :
- ; |xxxx|cccc|cccc|cc??|
- ; xxxx = count of char in string
- ; cccc = two packed char in one word
- *
- I:R TCHAR ; temp version of char
- *
- * DATA STATEMENT
- *
- V:S MAXNDX = '80'
- V:S TRUE = -1
- V:S FALSE = 0
- *
- ************************************************************************
- * START OF EXECUTABLE CODE
- ************************************************************************
- *
- E:O PACKLINE.(CHAR,ARRAY)
- *
- W:R ARRAY(0).UGE.MAXNDX
- STAT = TRUE
- O:E
- W:R CHAR .L. 0
- TCHAR = CHAR .RSH. 8
- O:E
- TCHAR = CHAR .LAND. '7F' .LOR. '80' ; MAKE IT CGOS FORMAT
- E:L
- E'E STBYTT.(TCHAR, ARRAY(1), ARRAY(0))
- ARRAY(0) = ARRAY(0) + 1
- W:R ARRAY(0).UL.MAXNDX
- STAT = FALSE
- O:E
- STAT = TRUE
- E:L
- E:L
- # W:R ARRAY(0) .UGE. MAXNDX , E:E HEXDMP.(1,1,1,ARRAY(0))
- F:N STAT
- *
- ************************************************************************
- *
- E:O EMPTLINE.(CHAR,ARRAY)
- *
- W:R ARRAY(0).E.0, F'N TRUE ; EMPTY ARRAY
- ARRAY(0) = ARRAY(0) - 1
- ; pull char out of array from front to back
- CHAR = LDBYTT.(ARRAY(1), MAXNDX - ARRAY(0))
- W:R ARRAY(0).NE.0
- STAT = FALSE
- O:E
- STAT = TRUE
- E:L
- F:N STAT
- *
- E:N
- <<< KERMIT.UNCHAR >>>
- ; 18 jly 85 esj converted
- ;;;;;;; UNCHAR ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- E'F
- E'O UNCHAR.(CH)
-
- /INCLUDE BYU.PROG.KERMIT.SYM.EQU.KERDEF
-
- F'N (CH-BLANK)
-
- E'N
- <<< KERMIT.VERSION-LOG >>>
- * 26 aug 85 esj v1.21 made loadlib.kermit to remove the last of the cgos work
- * pack dependences. (i hope) also added debug flag
- * 18 aug 85 esj v1.20 removed s.e.fm.error.uil references and made fewer
- * cgos workpack dependences.
- * 16 aug 85 esj/pcc v1.19 removed server commands as aliases.
- * added formatting around sending messages.
- * added formatting around receiving messages.
- * allow device names selected by set line to
- * begin with non alfa characters.
- * 15 aug 85 mvi/esj v1.18a sconnect and no wait io mods to prevent
- * sconnect keep from dropping characters
- * 13 aug 85 esj v1.18 added aliases for: quit,receive,connect
- * made connect state the actual char to be typed for leaving
- * connect mode.
- * 12 aug 85 esj v1.17 converted to cvcommand for submission to master pack
- * 7 aug 85 esj v1.16 added send @filename, AND first public release
- * 7 aug 85 dg/esj v1.15 add support for no wait io in tputch and putlin
- * 6 aug 85 esj v1.14 fixed the printing of dots when a packet is received to
- * a routine of its own. Also made it add a crlf at 80 char limit
- * changed messages for sending and getting files.
- * added "waiting <n> seconds" to ssend when in remote mode.
- * 6 aug 85 esj V1.13 created
- *----------------------------< version-log >-----------------------------
- *
- * This file contains the version number for kermit. This must be included with
- * every submission.
-
- global vernum(5)
- set vernum = " V1.21!"
-
- * debug is a symbol to control conditional loading in the kermit make
- * file. if debug = 0 then debugging is off. if debug = -1 the debugging is
- * on
- equ debug = 0
- <<< KERMIT.XDELAY >>>
- ; 22 jly esj converted
- ;;;;;;;;;;;;;;;;;;; XDELAY ;;;;;;;;;;;;;;;;;;;C
- E'F A:S(NWLS)
- E'O XDELAY.(X)
-
- ; delay the calling program for x seconds
-
-
- E'E HIBERN8.(100*X)
- F'N
- E'N
- <<< KERMIT.SYM.EQU.KERCOM >>>
- ; 22 jly 85 esj converted and eliminated uneeded globals
- ;;;;;;;;;;;;;; KERCOM ;;;;;;;;;;;;;;;;;;;;;;;
- ; DEFINITION OF KEY GLOBAL VARIABLES FOLLOWS:
-
- ; DELAY - # of seconds waited before sending out the first
- ; - SINIT packet ( only in remote mode).
- ; EOL - End of line delimiter required by other KERMITS.
- ; ESCHAR - The character used to return back to command parser
- ; - from 'CHAT' mode.
- ; FD - The file descriptor of sending/receiving
- ; - file
- ; FILNAME(*) - The integer array which holds The currrent working
- ; - filename
- ; HOSTON - Identifies whether this KERMIT is running in local
- ; - or remote mode.
- ; IBMON - Identifies whether this KERMIT is talking to an
- ; - IBM CMS system.
- ; MAXTRY - Maximum number of re-try before giving up
- ; MYEOL - The end of line delimiter selectable by users
- ; MYPAD - The # of pad characters required by this KERMIT
- ; MYPCHAR - The pad character required by this KERMIT
- ; MYQUOTE - The quote used for control s
- ; - by this KERMIT slectable by user
- ; N - The number of the current packet frame number
- ; NUMTRY - The number of re-try attempt so far
- ; OLDTRY - The number of re-try already attempted
- ; PACKET(*) - An integer array to hold the content of a packet
- ; PAD - The # of pad characters required by other KERMIT
- ; PADCHAR - The pad character to used if required by other KERM
- ; PAKSIZ - The maximum packet size selectable by users
- ; PROMPT - The turnaround control character this KERMIT looks
- ; - for in file transfer with IBM.
- ; QUOTE - The quote character used for control character used
- ; - by other KERMITS
- ; RECPKT(*) - An integer array which holds the incoming packet
- ; RMTDEV(*) - The remote (TTY) line KM will be the default name
- ; - RMTDEV(1) = IOFLAG FOR THE UNIT
- ; LOCALDEV(*)- Local (tty) (login line) SD is the device name
- ; - LOCALDEV(1) = IOFLAG FOR THE UNIT
- ; RMTTTY(*) - An integer array which hold the un-login line
- ; - for file-transfer.
- ; RPSIZ - maximum size of packet to be receive
- ; SBAUD - whether this system supports baud switching
- ; SIZE - maximum size of data packet to be sent
- ; SOH - The start of header used in sending packet; selecta
- ; - by user
- ; SPARITY - whether this system supports parity switching
- ; SPORT - whether this system supports remote line switching
- ; SPSIZ - Maximum size of packet to be used for sending
- ; STATE - Current state of file transfer processs
-
-
- G'L DELAY,EOL,ESCHAR,FD(*),FILNAME(*),HOSTON
- G'L IBMON,MAXTRY
- G'L MYEOL,MYPAD,MYPCHAR,MYQUOTE,N,NUMTRY,OLDTRY
- G'L PACKET(*),PAD,PADCHAR,PAKSIZ,PROMPT
- G'L QUOTE,RECPKT(*),RMTDEV(*),RMTTTY(*)
- G'L RPSIZ,SBAUD,SIZE,SOH,SPARITY,SPORT,SPSIZ
- G'L STATE
- G'L LOCALDEV(*) ; replaced --> LOCALINFD
- ; NOT USED --> LOCALOUTFD
- <<< KERMIT.SYM.EQU.KERDEF >>>
- ; 19 aug 85 esj added fm error constants as teq in case they really get
- ; included
- ; 23 jly 85 esj oops, equs need hex constant, not decimal
- ; 16 jly 85 esj renamed constants with excessive size.
- ;;;;;;;;;;;;;; KERDEF ;;;;;;;;;;;;;;;;;;;;;;;
- ; DEFINES VARIOUS CONSTANTS FOR THE KERMIT-CGOS PROGRAM
- EQU BACKSLSH = 5C ; replaced --> BACKSLASH = 92
- EQU BACKSPCE = 8 ; replaced --> BACKSPACE = 8
- EQU GOOD = 0
- EQU BAD = 8000
- EQU BANG = 21
- EQU BAR = 7C ;
- EQU ATSIGN = 40
- EQU BIGA = 41
- EQU BIGB = 42
- EQU BIGC = 43
- EQU BIGD = 44
- EQU BIGE = 45
- EQU BIGF = 46
- EQU BIGG = 47
- EQU BIGH = 48
- EQU BIGI = 49
- EQU BIGJ = 4A
- EQU BIGK = 4B
- EQU BIGL = 4C
- EQU BIGM = 4D
- EQU BIGN = 4E
- EQU BIGO = 4F
- EQU BIGP = 50
- EQU BIGQ = 51
- EQU BIGR = 52
- EQU BIGS = 53
- EQU BIGT = 54
- EQU BIGU = 55
- EQU BIGV = 56
- EQU BIGW = 57
- EQU BIGX = 58
- EQU BIGY = 59
- EQU BIGZ = 5A
- EQU BLANK = 20
- EQU CARET = 5E
- EQU COLON = 3A
- EQU COMMA = 2C
- EQU CR = 0D
- EQU DEL = 7F
- EQU DIG0 = 30
- EQU DIG1 = 31
- EQU DIG2 = 32
- EQU DIG3 = 33
- EQU DIG4 = 34
- EQU DIG5 = 35
- EQU DIG6 = 36
- EQU DIG7 = 37
- EQU DIG8 = 38
- EQU DIG9 = 39
- EQU DIGIT = 2
- EQU DOLLAR = 24
- EQU DQUOTE = 22
- EQU EOF = -1
- EQU EOS = -8
- EQU LETA = 61
- EQU LETB = 62
- EQU LETC = 63
- EQU LETD = 64
- EQU LETE = 65
- EQU LETF = 66
- EQU LETG = 67
- EQU LETH = 68
- EQU LETI = 69
- EQU LETJ = 6A
- EQU LETK = 6B
- EQU LETL = 6C
- EQU LETM = 6D
- EQU LETN = 6E
- EQU LETO = 6F
- EQU LETP = 70
- EQU LETQ = 71
- EQU LETR = 72
- EQU LETS = 73
- EQU LETT = 74
- EQU LETU = 75
- EQU LETV = 76
- EQU LETW = 77
- EQU LETX = 78
- EQU LETY = 79
- EQU LETZ = 7A
- EQU LF = 0A
- EQU NO = 0
- EQU OK = -2
- EQU PERCENT = 25
- EQU PERIOD = 2E
- EQU PLUS = 2B
- EQU QMARK = 3F
- EQU SEMICOL = 3B
- EQU SHARP = 23
- EQU SLASH = 2F
- EQU SQUOTE = 27
- EQU STAR = 2A
- EQU STDOUT = 1
- EQU TAB = 9
- EQU TILDE = 7E
- EQU UNDRLINE = 5F ; replaced --> UNDERLINE = 95
- EQU YES = 1
-
- ; FM ERROR CONSTANTS
-
- ASSM
-
- TEQ FM%NOERR = 0000 ; Everything is fine.
- TEQ UL%RDEOF = 0C5F9 ; Attempt to read record at
- ; End Of File
-
- ENDA
-